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

Test.Syd.Def.TestDefM

Synopsis

Documentation

type Spec = SpecWith () Source #

A synonym for easy migration from hspec

type SpecWith inner = SpecM inner () Source #

A synonym for easy migration from hspec

type SpecM inner result = TestDefM '[] inner result Source #

A synonym for easy migration from hspec

type TestDef outers inner = TestDefM outers inner () Source #

A synonym for a test suite definition

newtype TestDefM (outers :: [Type]) inner result Source #

The test definition monad

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.

Constructors

TestDefM 

Fields

Instances

Instances details
MonadReader TestDefEnv (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

ask :: TestDefM outers inner TestDefEnv #

local :: (TestDefEnv -> TestDefEnv) -> TestDefM outers inner a -> TestDefM outers inner a #

reader :: (TestDefEnv -> a) -> TestDefM outers inner a #

Monad (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

(>>=) :: TestDefM outers inner a -> (a -> TestDefM outers inner b) -> TestDefM outers inner b #

(>>) :: TestDefM outers inner a -> TestDefM outers inner b -> TestDefM outers inner b #

return :: a -> TestDefM outers inner a #

Functor (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

fmap :: (a -> b) -> TestDefM outers inner a -> TestDefM outers inner b #

(<$) :: a -> TestDefM outers inner b -> TestDefM outers inner a #

Applicative (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

pure :: a -> TestDefM outers inner a #

(<*>) :: TestDefM outers inner (a -> b) -> TestDefM outers inner a -> TestDefM outers inner b #

liftA2 :: (a -> b -> c) -> TestDefM outers inner a -> TestDefM outers inner b -> TestDefM outers inner c #

(*>) :: TestDefM outers inner a -> TestDefM outers inner b -> TestDefM outers inner b #

(<*) :: TestDefM outers inner a -> TestDefM outers inner b -> TestDefM outers inner a #

MonadIO (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

liftIO :: IO a -> TestDefM outers inner a #

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 #

data TestDefEnv Source #

Instances

Instances details
Eq TestDefEnv Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Show TestDefEnv Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Generic TestDefEnv Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Associated Types

type Rep TestDefEnv :: Type -> Type #

MonadReader TestDefEnv (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

ask :: TestDefM outers inner TestDefEnv #

local :: (TestDefEnv -> TestDefEnv) -> TestDefM outers inner a -> TestDefM outers inner a #

reader :: (TestDefEnv -> a) -> TestDefM outers inner a #

type Rep TestDefEnv Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

type Rep TestDefEnv = D1 ('MetaData "TestDefEnv" "Test.Syd.Def.TestDefM" "sydtest-0.10.0.0-3hbJHNppGEOJTpttnKeKQH" 'False) (C1 ('MetaCons "TestDefEnv" 'PrefixI 'True) (S1 ('MetaSel ('Just "testDefEnvDescriptionPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "testDefEnvTestRunSettings") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TestRunSettings)))

execTestDefM :: Settings -> TestDefM outers inner result -> IO (TestForest outers inner) Source #

runTestDefM :: Settings -> TestDefM outers inner result -> IO (result, TestForest outers inner) Source #

getTestDescriptionPath :: TestDefM outers inner [Text] Source #

Get the path of describe strings upwards.

Note that using this function makes tests less movable, depending on what you do with these strings. For example, if you use these strings to define the path to a golden test file, then that path will change if you move the tests somewhere else. This combines unfortunately with the way sydtest-discover makes the module name part of this path. Indeed: moving your tests to another module will change their path as well, if you use sydtest-discover. Also note that while test forests can be randomised, their description path upwards will not, because of how trees are structured.