{-# LANGUAGE Safe #-}
module Types.IntegrationTest (
ExpectedResult(..),
IntegrationTest(..),
IntegrationTestHeader(..),
OutputPattern(..),
OutputScope(..),
getExcludePattern,
getRequirePattern,
isExpectCompilerError,
isExpectCompiles,
isExpectRuntimeError,
isExpectRuntimeSuccess,
) where
import Types.TypeCategory
import Types.TypeInstance
import Types.DefinedCategory
import Types.Procedure
data c =
{
forall c. IntegrationTestHeader c -> [c]
ithContext :: [c],
forall c. IntegrationTestHeader c -> String
ithTestName :: String,
forall c. IntegrationTestHeader c -> [String]
ithArgs :: [String],
forall c. IntegrationTestHeader c -> Maybe Integer
ithTimeout :: Maybe Integer,
forall c. IntegrationTestHeader c -> ExpectedResult c
ithResult :: ExpectedResult c
}
data IntegrationTest c =
IntegrationTest {
:: IntegrationTestHeader c,
forall c. IntegrationTest c -> [AnyCategory c]
itCategory :: [AnyCategory c],
forall c. IntegrationTest c -> [DefinedCategory c]
itDefinition :: [DefinedCategory c],
forall c. IntegrationTest c -> [TestProcedure c]
itTests :: [TestProcedure c]
}
data ExpectedResult c =
ExpectCompilerError {
forall c. ExpectedResult c -> [c]
eceContext :: [c],
forall c. ExpectedResult c -> [OutputPattern]
eceRequirePattern :: [OutputPattern],
forall c. ExpectedResult c -> [OutputPattern]
eceExcludePattern :: [OutputPattern]
} |
ExpectCompiles {
eceContext :: [c],
eceRequirePattern :: [OutputPattern],
eceExcludePattern :: [OutputPattern]
} |
ExpectRuntimeError {
forall c. ExpectedResult c -> [c]
ereContext :: [c],
forall c. ExpectedResult c -> Maybe ([c], TypeInstance)
ereCategory :: Maybe ([c],TypeInstance),
forall c. ExpectedResult c -> [OutputPattern]
ereRequirePattern :: [OutputPattern],
forall c. ExpectedResult c -> [OutputPattern]
ereExcludePattern :: [OutputPattern]
} |
ExpectRuntimeSuccess {
forall c. ExpectedResult c -> [c]
ersContext :: [c],
forall c. ExpectedResult c -> Maybe ([c], TypeInstance)
ersCategory :: Maybe ([c],TypeInstance),
forall c. ExpectedResult c -> [OutputPattern]
ersRequirePattern :: [OutputPattern],
forall c. ExpectedResult c -> [OutputPattern]
ersExcludePattern :: [OutputPattern]
}
data OutputPattern =
OutputPattern {
OutputPattern -> OutputScope
opScope :: OutputScope,
OutputPattern -> String
opPattern :: String
}
deriving (OutputPattern -> OutputPattern -> Bool
(OutputPattern -> OutputPattern -> Bool)
-> (OutputPattern -> OutputPattern -> Bool) -> Eq OutputPattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutputPattern -> OutputPattern -> Bool
== :: OutputPattern -> OutputPattern -> Bool
$c/= :: OutputPattern -> OutputPattern -> Bool
/= :: OutputPattern -> OutputPattern -> Bool
Eq,Eq OutputPattern
Eq OutputPattern =>
(OutputPattern -> OutputPattern -> Ordering)
-> (OutputPattern -> OutputPattern -> Bool)
-> (OutputPattern -> OutputPattern -> Bool)
-> (OutputPattern -> OutputPattern -> Bool)
-> (OutputPattern -> OutputPattern -> Bool)
-> (OutputPattern -> OutputPattern -> OutputPattern)
-> (OutputPattern -> OutputPattern -> OutputPattern)
-> Ord OutputPattern
OutputPattern -> OutputPattern -> Bool
OutputPattern -> OutputPattern -> Ordering
OutputPattern -> OutputPattern -> OutputPattern
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: OutputPattern -> OutputPattern -> Ordering
compare :: OutputPattern -> OutputPattern -> Ordering
$c< :: OutputPattern -> OutputPattern -> Bool
< :: OutputPattern -> OutputPattern -> Bool
$c<= :: OutputPattern -> OutputPattern -> Bool
<= :: OutputPattern -> OutputPattern -> Bool
$c> :: OutputPattern -> OutputPattern -> Bool
> :: OutputPattern -> OutputPattern -> Bool
$c>= :: OutputPattern -> OutputPattern -> Bool
>= :: OutputPattern -> OutputPattern -> Bool
$cmax :: OutputPattern -> OutputPattern -> OutputPattern
max :: OutputPattern -> OutputPattern -> OutputPattern
$cmin :: OutputPattern -> OutputPattern -> OutputPattern
min :: OutputPattern -> OutputPattern -> OutputPattern
Ord,Int -> OutputPattern -> ShowS
[OutputPattern] -> ShowS
OutputPattern -> String
(Int -> OutputPattern -> ShowS)
-> (OutputPattern -> String)
-> ([OutputPattern] -> ShowS)
-> Show OutputPattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OutputPattern -> ShowS
showsPrec :: Int -> OutputPattern -> ShowS
$cshow :: OutputPattern -> String
show :: OutputPattern -> String
$cshowList :: [OutputPattern] -> ShowS
showList :: [OutputPattern] -> ShowS
Show)
data OutputScope = OutputAny | OutputCompiler | OutputStderr | OutputStdout deriving (OutputScope -> OutputScope -> Bool
(OutputScope -> OutputScope -> Bool)
-> (OutputScope -> OutputScope -> Bool) -> Eq OutputScope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutputScope -> OutputScope -> Bool
== :: OutputScope -> OutputScope -> Bool
$c/= :: OutputScope -> OutputScope -> Bool
/= :: OutputScope -> OutputScope -> Bool
Eq,Eq OutputScope
Eq OutputScope =>
(OutputScope -> OutputScope -> Ordering)
-> (OutputScope -> OutputScope -> Bool)
-> (OutputScope -> OutputScope -> Bool)
-> (OutputScope -> OutputScope -> Bool)
-> (OutputScope -> OutputScope -> Bool)
-> (OutputScope -> OutputScope -> OutputScope)
-> (OutputScope -> OutputScope -> OutputScope)
-> Ord OutputScope
OutputScope -> OutputScope -> Bool
OutputScope -> OutputScope -> Ordering
OutputScope -> OutputScope -> OutputScope
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: OutputScope -> OutputScope -> Ordering
compare :: OutputScope -> OutputScope -> Ordering
$c< :: OutputScope -> OutputScope -> Bool
< :: OutputScope -> OutputScope -> Bool
$c<= :: OutputScope -> OutputScope -> Bool
<= :: OutputScope -> OutputScope -> Bool
$c> :: OutputScope -> OutputScope -> Bool
> :: OutputScope -> OutputScope -> Bool
$c>= :: OutputScope -> OutputScope -> Bool
>= :: OutputScope -> OutputScope -> Bool
$cmax :: OutputScope -> OutputScope -> OutputScope
max :: OutputScope -> OutputScope -> OutputScope
$cmin :: OutputScope -> OutputScope -> OutputScope
min :: OutputScope -> OutputScope -> OutputScope
Ord,Int -> OutputScope -> ShowS
[OutputScope] -> ShowS
OutputScope -> String
(Int -> OutputScope -> ShowS)
-> (OutputScope -> String)
-> ([OutputScope] -> ShowS)
-> Show OutputScope
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OutputScope -> ShowS
showsPrec :: Int -> OutputScope -> ShowS
$cshow :: OutputScope -> String
show :: OutputScope -> String
$cshowList :: [OutputScope] -> ShowS
showList :: [OutputScope] -> ShowS
Show)
isExpectCompiles :: ExpectedResult c -> Bool
isExpectCompiles :: forall c. ExpectedResult c -> Bool
isExpectCompiles (ExpectCompiles [c]
_ [OutputPattern]
_ [OutputPattern]
_) = Bool
True
isExpectCompiles ExpectedResult c
_ = Bool
False
isExpectCompilerError :: ExpectedResult c -> Bool
isExpectCompilerError :: forall c. ExpectedResult c -> Bool
isExpectCompilerError (ExpectCompilerError [c]
_ [OutputPattern]
_ [OutputPattern]
_) = Bool
True
isExpectCompilerError ExpectedResult c
_ = Bool
False
isExpectRuntimeError :: ExpectedResult c -> Bool
isExpectRuntimeError :: forall c. ExpectedResult c -> Bool
isExpectRuntimeError (ExpectRuntimeError [c]
_ Maybe ([c], TypeInstance)
_ [OutputPattern]
_ [OutputPattern]
_) = Bool
True
isExpectRuntimeError ExpectedResult c
_ = Bool
False
isExpectRuntimeSuccess :: ExpectedResult c -> Bool
isExpectRuntimeSuccess :: forall c. ExpectedResult c -> Bool
isExpectRuntimeSuccess (ExpectRuntimeSuccess [c]
_ Maybe ([c], TypeInstance)
_ [OutputPattern]
_ [OutputPattern]
_) = Bool
True
isExpectRuntimeSuccess ExpectedResult c
_ = Bool
False
getRequirePattern :: ExpectedResult c -> [OutputPattern]
getRequirePattern :: forall c. ExpectedResult c -> [OutputPattern]
getRequirePattern (ExpectCompiles [c]
_ [OutputPattern]
rs [OutputPattern]
_) = [OutputPattern]
rs
getRequirePattern (ExpectCompilerError [c]
_ [OutputPattern]
rs [OutputPattern]
_) = [OutputPattern]
rs
getRequirePattern (ExpectRuntimeError [c]
_ Maybe ([c], TypeInstance)
_ [OutputPattern]
rs [OutputPattern]
_) = [OutputPattern]
rs
getRequirePattern (ExpectRuntimeSuccess [c]
_ Maybe ([c], TypeInstance)
_ [OutputPattern]
rs [OutputPattern]
_) = [OutputPattern]
rs
getExcludePattern :: ExpectedResult c -> [OutputPattern]
getExcludePattern :: forall c. ExpectedResult c -> [OutputPattern]
getExcludePattern (ExpectCompiles [c]
_ [OutputPattern]
_ [OutputPattern]
es) = [OutputPattern]
es
getExcludePattern (ExpectCompilerError [c]
_ [OutputPattern]
_ [OutputPattern]
es) = [OutputPattern]
es
getExcludePattern (ExpectRuntimeError [c]
_ Maybe ([c], TypeInstance)
_ [OutputPattern]
_ [OutputPattern]
es) = [OutputPattern]
es
getExcludePattern (ExpectRuntimeSuccess [c]
_ Maybe ([c], TypeInstance)
_ [OutputPattern]
_ [OutputPattern]
es) = [OutputPattern]
es