Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test.Syd.SpecDef
Description
This module defines all the functions you will use to define your test suite.
Synopsis
- data TDef value = TDef {
- testDefVal :: value
- testDefCallStack :: CallStack
- type TestForest outers inner = SpecDefForest outers inner ()
- type TestTree outers inner = SpecDefTree outers inner ()
- type SpecDefForest (outers :: [Type]) inner extra = [SpecDefTree outers inner extra]
- data SpecDefTree (outers :: [Type]) inner extra where
- DefSpecifyNode :: Text -> TDef (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult) -> extra -> SpecDefTree outers inner extra
- DefPendingNode :: Text -> Maybe Text -> SpecDefTree outers inner extra
- DefDescribeNode :: Text -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefWrapNode :: (IO () -> IO ()) -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefBeforeAllNode :: IO outer -> SpecDefForest (outer ': otherOuters) inner extra -> SpecDefTree otherOuters inner extra
- DefAroundAllNode :: ((outer -> IO ()) -> IO ()) -> SpecDefForest (outer ': otherOuters) inner extra -> SpecDefTree otherOuters inner extra
- DefAroundAllWithNode :: ((newOuter -> IO ()) -> oldOuter -> IO ()) -> SpecDefForest (newOuter ': (oldOuter ': otherOuters)) inner extra -> SpecDefTree (oldOuter ': otherOuters) inner extra
- DefAfterAllNode :: (HList outers -> IO ()) -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefParallelismNode :: Parallelism -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefRandomisationNode :: ExecutionOrderRandomisation -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- data Parallelism
- data ExecutionOrderRandomisation
- type ResultForest = SpecForest (TDef (Timed TestRunResult))
- type ResultTree = SpecTree (TDef (Timed TestRunResult))
- computeTestSuiteStats :: ResultForest -> TestSuiteStats
- data TestSuiteStats = TestSuiteStats {}
- shouldExitFail :: ResultForest -> Bool
Documentation
Constructors
TDef | |
Fields
|
Instances
Functor TDef Source # | |
Foldable TDef Source # | |
Defined in Test.Syd.SpecDef Methods fold :: Monoid m => TDef m -> m # foldMap :: Monoid m => (a -> m) -> TDef a -> m # foldMap' :: Monoid m => (a -> m) -> TDef a -> m # foldr :: (a -> b -> b) -> b -> TDef a -> b # foldr' :: (a -> b -> b) -> b -> TDef a -> b # foldl :: (b -> a -> b) -> b -> TDef a -> b # foldl' :: (b -> a -> b) -> b -> TDef a -> b # foldr1 :: (a -> a -> a) -> TDef a -> a # foldl1 :: (a -> a -> a) -> TDef a -> a # elem :: Eq a => a -> TDef a -> Bool # maximum :: Ord a => TDef a -> a # | |
Traversable TDef Source # | |
type TestForest outers inner = SpecDefForest outers inner () Source #
type TestTree outers inner = SpecDefTree outers inner () Source #
type SpecDefForest (outers :: [Type]) inner extra = [SpecDefTree outers inner extra] Source #
data SpecDefTree (outers :: [Type]) inner extra where Source #
A tree of tests
This type has three parameters:
outers
: A type-level list of the outer resources. These are resources that are prived once, around a group of tests. (This is the type of the results ofaroundAll
.)inner
: The inner resource. This is a resource that is set up around every test, and even every example of a property test. (This is the type of the result ofaround
.)result
: The result (TestDefM
is a monad.)
In practice, all of these three parameters should be ()
at the top level.
When you're just using sydtest and not writing a library for sydtest, you probably don't even want to concern yourself with this type.
Constructors
DefSpecifyNode | Define a test |
Fields
| |
DefPendingNode | Define a pending test |
Fields
| |
DefDescribeNode | Group tests using a description |
Fields
| |
DefWrapNode | |
Fields
| |
DefBeforeAllNode | |
Fields
| |
DefAroundAllNode | |
Fields
| |
DefAroundAllWithNode | |
Fields
| |
DefAfterAllNode | |
Fields
| |
DefParallelismNode | Control the level of parallelism for a given group of tests |
Fields
| |
DefRandomisationNode | Control the execution order randomisation for a given group of tests |
Fields
|
Instances
Functor (SpecDefTree a c) Source # | |
Defined in Test.Syd.SpecDef Methods fmap :: (a0 -> b) -> SpecDefTree a c a0 -> SpecDefTree a c b # (<$) :: a0 -> SpecDefTree a c b -> SpecDefTree a c a0 # | |
Foldable (SpecDefTree a c) Source # | |
Defined in Test.Syd.SpecDef Methods fold :: Monoid m => SpecDefTree a c m -> m # foldMap :: Monoid m => (a0 -> m) -> SpecDefTree a c a0 -> m # foldMap' :: Monoid m => (a0 -> m) -> SpecDefTree a c a0 -> m # foldr :: (a0 -> b -> b) -> b -> SpecDefTree a c a0 -> b # foldr' :: (a0 -> b -> b) -> b -> SpecDefTree a c a0 -> b # foldl :: (b -> a0 -> b) -> b -> SpecDefTree a c a0 -> b # foldl' :: (b -> a0 -> b) -> b -> SpecDefTree a c a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> SpecDefTree a c a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> SpecDefTree a c a0 -> a0 # toList :: SpecDefTree a c a0 -> [a0] # null :: SpecDefTree a c a0 -> Bool # length :: SpecDefTree a c a0 -> Int # elem :: Eq a0 => a0 -> SpecDefTree a c a0 -> Bool # maximum :: Ord a0 => SpecDefTree a c a0 -> a0 # minimum :: Ord a0 => SpecDefTree a c a0 -> a0 # sum :: Num a0 => SpecDefTree a c a0 -> a0 # product :: Num a0 => SpecDefTree a c a0 -> a0 # | |
Traversable (SpecDefTree a c) Source # | |
Defined in Test.Syd.SpecDef Methods traverse :: Applicative f => (a0 -> f b) -> SpecDefTree a c a0 -> f (SpecDefTree a c b) # sequenceA :: Applicative f => SpecDefTree a c (f a0) -> f (SpecDefTree a c a0) # mapM :: Monad m => (a0 -> m b) -> SpecDefTree a c a0 -> m (SpecDefTree a c b) # sequence :: Monad m => SpecDefTree a c (m a0) -> m (SpecDefTree a c a0) # | |
MonadWriter (TestForest outers inner) (TestDefM outers inner) Source # | |
Defined in Test.Syd.Def.TestDefM Methods writer :: (a, TestForest outers inner) -> TestDefM outers inner a # tell :: TestForest outers inner -> TestDefM outers inner () # listen :: TestDefM outers inner a -> TestDefM outers inner (a, TestForest outers inner) # pass :: TestDefM outers inner (a, TestForest outers inner -> TestForest outers inner) -> TestDefM outers inner a # |
data Parallelism Source #
Constructors
Parallel | |
Sequential |
data ExecutionOrderRandomisation Source #
Constructors
RandomiseExecutionOrder | |
DoNotRandomiseExecutionOrder |
type ResultForest = SpecForest (TDef (Timed TestRunResult)) Source #
type ResultTree = SpecTree (TDef (Timed TestRunResult)) Source #
data TestSuiteStats Source #
Constructors
TestSuiteStats | |
Fields
|
Instances
Eq TestSuiteStats Source # | |
Defined in Test.Syd.SpecDef Methods (==) :: TestSuiteStats -> TestSuiteStats -> Bool # (/=) :: TestSuiteStats -> TestSuiteStats -> Bool # | |
Show TestSuiteStats Source # | |
Defined in Test.Syd.SpecDef Methods showsPrec :: Int -> TestSuiteStats -> ShowS # show :: TestSuiteStats -> String # showList :: [TestSuiteStats] -> ShowS # | |
Semigroup TestSuiteStats Source # | |
Defined in Test.Syd.SpecDef Methods (<>) :: TestSuiteStats -> TestSuiteStats -> TestSuiteStats # sconcat :: NonEmpty TestSuiteStats -> TestSuiteStats # stimes :: Integral b => b -> TestSuiteStats -> TestSuiteStats # | |
Monoid TestSuiteStats Source # | |
Defined in Test.Syd.SpecDef Methods mappend :: TestSuiteStats -> TestSuiteStats -> TestSuiteStats # mconcat :: [TestSuiteStats] -> TestSuiteStats # |
shouldExitFail :: ResultForest -> Bool Source #