{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.TestSuite
( TestInstance(..)
, OptionDescr(..)
, OptionType(..)
, Test(..)
, Options
, Progress(..)
, Result(..)
, testGroup
) where
import Prelude ()
import Distribution.Compat.Prelude
data TestInstance = TestInstance
{ TestInstance -> IO Progress
Evidence bound by a HsWrapper of the constraint type HasCallStack
Evidence bound by a HsWrapper of the constraint type HasCallStack
run :: IO Progress
, TestInstance -> String
name :: String
, TestInstance -> [String]
tags :: [String]
, TestInstance -> [OptionDescr]
options :: [OptionDescr]
, TestInstance -> String -> String -> Either String TestInstance
setOption :: String -> String -> Either String TestInstance
}
data OptionDescr = OptionDescr
{ OptionDescr -> String
optionName :: String
, OptionDescr -> String
optionDescription :: String
, OptionDescr -> OptionType
optionType :: OptionType
, OptionDescr -> Maybe String
optionDefault :: Maybe String
}
deriving (OptionDescr -> OptionDescr -> Bool
(OptionDescr -> OptionDescr -> Bool)
-> (OptionDescr -> OptionDescr -> Bool) -> Eq OptionDescr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptionDescr -> OptionDescr -> Bool
$c/= :: OptionDescr -> OptionDescr -> Bool
== :: OptionDescr -> OptionDescr -> Bool
$c== :: OptionDescr -> OptionDescr -> Bool
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
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 forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
Instance of class: Eq of the constraint type Eq OptionType
Eq, ReadPrec [OptionDescr]
ReadPrec OptionDescr
Int -> ReadS OptionDescr
ReadS [OptionDescr]
(Int -> ReadS OptionDescr)
-> ReadS [OptionDescr]
-> ReadPrec OptionDescr
-> ReadPrec [OptionDescr]
-> Read OptionDescr
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OptionDescr]
$creadListPrec :: ReadPrec [OptionDescr]
readPrec :: ReadPrec OptionDescr
$creadPrec :: ReadPrec OptionDescr
readList :: ReadS [OptionDescr]
$creadList :: ReadS [OptionDescr]
readsPrec :: Int -> ReadS OptionDescr
$creadsPrec :: Int -> ReadS OptionDescr
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read (Maybe a)
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 forall a. Read a => Read [a]
External instance of the constraint type Read Char
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 OptionType
Instance of class: Read of the constraint type Read OptionDescr
Read, Int -> OptionDescr -> ShowS
[OptionDescr] -> ShowS
OptionDescr -> String
(Int -> OptionDescr -> ShowS)
-> (OptionDescr -> String)
-> ([OptionDescr] -> ShowS)
-> Show OptionDescr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptionDescr] -> ShowS
$cshowList :: [OptionDescr] -> ShowS
show :: OptionDescr -> String
$cshow :: OptionDescr -> String
showsPrec :: Int -> OptionDescr -> ShowS
$cshowsPrec :: Int -> OptionDescr -> ShowS
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show (Maybe a)
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 forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show OptionType
Show)
data OptionType
= OptionFile
{ OptionType -> Bool
optionFileMustExist :: Bool
, OptionType -> Bool
optionFileIsDir :: Bool
, OptionType -> [String]
optionFileExtensions :: [String]
}
| OptionString
{ OptionType -> Bool
optionStringMultiline :: Bool
}
| OptionNumber
{ OptionType -> Bool
optionNumberIsInt :: Bool
, OptionType -> (Maybe String, Maybe String)
optionNumberBounds :: (Maybe String, Maybe String)
}
| OptionBool
| OptionEnum [String]
| OptionSet [String]
| OptionRngSeed
deriving (OptionType -> OptionType -> Bool
(OptionType -> OptionType -> Bool)
-> (OptionType -> OptionType -> Bool) -> Eq OptionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptionType -> OptionType -> Bool
$c/= :: OptionType -> OptionType -> Bool
== :: OptionType -> OptionType -> Bool
$c== :: OptionType -> OptionType -> Bool
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type forall a. Eq a => Eq [a]
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 forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type Eq Bool
External instance of the constraint type Eq Bool
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type forall a. Eq a => Eq [a]
Eq, ReadPrec [OptionType]
ReadPrec OptionType
Int -> ReadS OptionType
ReadS [OptionType]
(Int -> ReadS OptionType)
-> ReadS [OptionType]
-> ReadPrec OptionType
-> ReadPrec [OptionType]
-> Read OptionType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OptionType]
$creadListPrec :: ReadPrec [OptionType]
readPrec :: ReadPrec OptionType
$creadPrec :: ReadPrec OptionType
readList :: ReadS [OptionType]
$creadList :: ReadS [OptionType]
readsPrec :: Int -> ReadS OptionType
$creadsPrec :: Int -> ReadS OptionType
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read (Maybe a)
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read (Maybe a)
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
External instance of the constraint type forall a. Read a => Read [a]
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 forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type Read Bool
External instance of the constraint type Read Bool
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read (Maybe a)
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read OptionType
Read, Int -> OptionType -> ShowS
[OptionType] -> ShowS
OptionType -> String
(Int -> OptionType -> ShowS)
-> (OptionType -> String)
-> ([OptionType] -> ShowS)
-> Show OptionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptionType] -> ShowS
$cshowList :: [OptionType] -> ShowS
show :: OptionType -> String
$cshow :: OptionType -> String
showsPrec :: Int -> OptionType -> ShowS
$cshowsPrec :: Int -> OptionType -> ShowS
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type forall a. Show a => Show [a]
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 forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Show Bool
External instance of the constraint type Show Bool
External instance of the constraint type Ord Int
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Ord Int
Show)
data Test
= Test TestInstance
| Group
{ Test -> String
groupName :: String
, Test -> Bool
concurrently :: Bool
, Test -> [Test]
groupTests :: [Test]
}
| [OptionDescr] Test
type Options = [(String, String)]
data Progress = Finished Result
| Progress String (IO Progress)
data Result = Pass
| Fail String
| Error String
deriving (Result -> Result -> Bool
(Result -> Result -> Bool)
-> (Result -> Result -> Bool) -> Eq Result
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Result -> Result -> Bool
$c/= :: Result -> Result -> Bool
== :: Result -> Result -> Bool
$c== :: Result -> Result -> Bool
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 Char
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
Eq, ReadPrec [Result]
ReadPrec Result
Int -> ReadS Result
ReadS [Result]
(Int -> ReadS Result)
-> ReadS [Result]
-> ReadPrec Result
-> ReadPrec [Result]
-> Read Result
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Result]
$creadListPrec :: ReadPrec [Result]
readPrec :: ReadPrec Result
$creadPrec :: ReadPrec Result
readList :: ReadS [Result]
$creadList :: ReadS [Result]
readsPrec :: Int -> ReadS Result
$creadsPrec :: Int -> ReadS Result
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 Char
External instance of the constraint type Monad ReadPrec
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 Monad ReadPrec
Instance of class: Read of the constraint type Read Result
Read, Int -> Result -> ShowS
[Result] -> ShowS
Result -> String
(Int -> Result -> ShowS)
-> (Result -> String) -> ([Result] -> ShowS) -> Show Result
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Result] -> ShowS
$cshowList :: [Result] -> ShowS
show :: Result -> String
$cshow :: Result -> String
showsPrec :: Int -> Result -> ShowS
$cshowsPrec :: Int -> Result -> ShowS
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 Char
External instance of the constraint type Ord Int
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 Ord Int
Show)
testGroup :: String -> [Test] -> Test
testGroup :: String -> [Test] -> Test
testGroup String
n [Test]
ts = Group :: String -> Bool -> [Test] -> Test
Group { groupName :: String
groupName = String
n, concurrently :: Bool
concurrently = Bool
True, groupTests :: [Test]
groupTests = [Test]
ts }