{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Distribution.Types.TestType (
TestType(..),
knownTestTypes,
) where
import Distribution.Compat.Prelude
import Distribution.Version
import Prelude ()
import Distribution.Parsec
import Distribution.Pretty
import Text.PrettyPrint (char, text)
data TestType = TestTypeExe Version
| TestTypeLib Version
| TestTypeUnknown String Version
deriving ((forall x. TestType -> Rep TestType x)
-> (forall x. Rep TestType x -> TestType) -> Generic TestType
forall x. Rep TestType x -> TestType
forall x. TestType -> Rep TestType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestType x -> TestType
$cfrom :: forall x. TestType -> Rep TestType x
Generic, Int -> TestType -> ShowS
[TestType] -> ShowS
TestType -> String
(Int -> TestType -> ShowS)
-> (TestType -> String) -> ([TestType] -> ShowS) -> Show TestType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestType] -> ShowS
$cshowList :: [TestType] -> ShowS
show :: TestType -> String
$cshow :: TestType -> String
showsPrec :: Int -> TestType -> ShowS
$cshowsPrec :: Int -> TestType -> ShowS
External instance of the constraint type Show Char
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Version
External instance of the constraint type Show Version
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
Show, ReadPrec [TestType]
ReadPrec TestType
Int -> ReadS TestType
ReadS [TestType]
(Int -> ReadS TestType)
-> ReadS [TestType]
-> ReadPrec TestType
-> ReadPrec [TestType]
-> Read TestType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TestType]
$creadListPrec :: ReadPrec [TestType]
readPrec :: ReadPrec TestType
$creadPrec :: ReadPrec TestType
readList :: ReadS [TestType]
$creadList :: ReadS [TestType]
readsPrec :: Int -> ReadS TestType
$creadsPrec :: Int -> ReadS TestType
External instance of the constraint type Read Char
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Version
External instance of the constraint type Read Version
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read TestType
Read, TestType -> TestType -> Bool
(TestType -> TestType -> Bool)
-> (TestType -> TestType -> Bool) -> Eq TestType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestType -> TestType -> Bool
$c/= :: TestType -> TestType -> Bool
== :: TestType -> TestType -> Bool
$c== :: TestType -> TestType -> Bool
External instance of the constraint type Eq Char
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Version
External instance of the constraint type Eq Version
Eq, Typeable, Typeable TestType
DataType
Constr
Typeable TestType
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TestType -> c TestType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TestType)
-> (TestType -> Constr)
-> (TestType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TestType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestType))
-> ((forall b. Data b => b -> b) -> TestType -> TestType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TestType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TestType -> r)
-> (forall u. (forall d. Data d => d -> u) -> TestType -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> TestType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TestType -> m TestType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TestType -> m TestType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TestType -> m TestType)
-> Data TestType
TestType -> DataType
TestType -> Constr
(forall b. Data b => b -> b) -> TestType -> TestType
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TestType -> c TestType
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TestType
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TestType -> u
forall u. (forall d. Data d => d -> u) -> TestType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TestType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TestType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TestType -> m TestType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TestType -> m TestType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TestType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TestType -> c TestType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TestType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestType)
$cTestTypeUnknown :: Constr
$cTestTypeLib :: Constr
$cTestTypeExe :: Constr
$tTestType :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> TestType -> m TestType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TestType -> m TestType
gmapMp :: (forall d. Data d => d -> m d) -> TestType -> m TestType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TestType -> m TestType
gmapM :: (forall d. Data d => d -> m d) -> TestType -> m TestType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TestType -> m TestType
gmapQi :: Int -> (forall d. Data d => d -> u) -> TestType -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TestType -> u
gmapQ :: (forall d. Data d => d -> u) -> TestType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TestType -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TestType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TestType -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TestType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TestType -> r
gmapT :: (forall b. Data b => b -> b) -> TestType -> TestType
$cgmapT :: (forall b. Data b => b -> b) -> TestType -> TestType
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestType)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TestType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TestType)
dataTypeOf :: TestType -> DataType
$cdataTypeOf :: TestType -> DataType
toConstr :: TestType -> Constr
$ctoConstr :: TestType -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TestType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TestType
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TestType -> c TestType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TestType -> c TestType
External instance of the constraint type Data Char
External instance of the constraint type Data Char
External instance of the constraint type Data Version
External instance of the constraint type Data Char
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Version
External instance of the constraint type Data Version
Data)
instance Binary TestType
instance Structured TestType
instance NFData TestType where rnf :: TestType -> ()
rnf = TestType -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData Version
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData Version
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData Version
Instance of class: Generic of the constraint type Generic TestType
genericRnf
knownTestTypes :: [TestType]
knownTestTypes :: [TestType]
knownTestTypes = [ Version -> TestType
TestTypeExe ([Int] -> Version
mkVersion [Int
1,Int
0])
, Version -> TestType
TestTypeLib ([Int] -> Version
mkVersion [Int
0,Int
9]) ]
instance Pretty TestType where
pretty :: TestType -> Doc
pretty (TestTypeExe Version
ver) = String -> Doc
text String
"exitcode-stdio-" Doc -> Doc -> Doc
<<>> Version -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty Version
pretty Version
ver
pretty (TestTypeLib Version
ver) = String -> Doc
text String
"detailed-" Doc -> Doc -> Doc
<<>> Version -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty Version
pretty Version
ver
pretty (TestTypeUnknown String
name Version
ver) = String -> Doc
text String
name Doc -> Doc -> Doc
<<>> Char -> Doc
char Char
'-' Doc -> Doc -> Doc
<<>> Version -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty Version
pretty Version
ver
instance Parsec TestType where
parsec :: m TestType
parsec = (Version -> String -> TestType) -> m TestType
forall (m :: * -> *) ver a.
(CabalParsing m, Parsec ver) =>
(ver -> String -> a) -> m a
External instance of the constraint type Parsec Version
Evidence bound by a type signature of the constraint type CabalParsing m
parsecStandard ((Version -> String -> TestType) -> m TestType)
-> (Version -> String -> TestType) -> m TestType
forall a b. (a -> b) -> a -> b
$ \Version
ver String
name -> case String
name of
String
"exitcode-stdio" -> Version -> TestType
TestTypeExe Version
ver
String
"detailed" -> Version -> TestType
TestTypeLib Version
ver
String
_ -> String -> Version -> TestType
TestTypeUnknown String
name Version
ver