sydtest-0.10.0.0: A modern testing framework for Haskell with good defaults and advanced testing features.
Safe HaskellNone
LanguageHaskell2010

Test.Syd.SpecDef

Description

This module defines all the functions you will use to define your test suite.

Synopsis

Documentation

data TDef value Source #

Constructors

TDef 

Instances

Instances details
Functor TDef Source # 
Instance details

Defined in Test.Syd.SpecDef

Methods

fmap :: (a -> b) -> TDef a -> TDef b #

(<$) :: a -> TDef b -> TDef a #

Foldable TDef Source # 
Instance details

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 #

toList :: TDef a -> [a] #

null :: TDef a -> Bool #

length :: TDef a -> Int #

elem :: Eq a => a -> TDef a -> Bool #

maximum :: Ord a => TDef a -> a #

minimum :: Ord a => TDef a -> a #

sum :: Num a => TDef a -> a #

product :: Num a => TDef a -> a #

Traversable TDef Source # 
Instance details

Defined in Test.Syd.SpecDef

Methods

traverse :: Applicative f => (a -> f b) -> TDef a -> f (TDef b) #

sequenceA :: Applicative f => TDef (f a) -> f (TDef a) #

mapM :: Monad m => (a -> m b) -> TDef a -> m (TDef b) #

sequence :: Monad m => TDef (m a) -> m (TDef a) #

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 of aroundAll.)
  • 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 of around.)
  • 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

  • :: IO outer

    The function to run (once), beforehand, to produce the outer resource.

  • -> SpecDefForest (outer ': otherOuters) inner extra
     
  • -> SpecDefTree otherOuters inner extra
     
DefAroundAllNode 

Fields

  • :: ((outer -> IO ()) -> IO ())

    The function that provides the outer resource (once), around the tests.

  • -> SpecDefForest (outer ': otherOuters) inner extra
     
  • -> SpecDefTree otherOuters inner extra
     
DefAroundAllWithNode 

Fields

  • :: ((newOuter -> IO ()) -> oldOuter -> IO ())

    The function that provides the new outer resource (once), using the old outer resource.

  • -> SpecDefForest (newOuter ': (oldOuter ': otherOuters)) inner extra
     
  • -> SpecDefTree (oldOuter ': otherOuters) inner extra
     
DefAfterAllNode 

Fields

  • :: (HList outers -> IO ())

    The function to run (once), afterwards, using all outer resources.

  • -> SpecDefForest outers inner extra
     
  • -> SpecDefTree outers inner extra
     
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

DefFlakinessNode 

Fields

Instances

Instances details
Functor (SpecDefTree a c) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 #

filterTestForest :: Maybe Text -> SpecDefForest outers inner result -> SpecDefForest outers inner result Source #

randomiseTestForest :: MonadRandom m => SpecDefForest outers inner result -> m (SpecDefForest outers inner result) Source #