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

Test.Syd.Def.SetupFunc

Synopsis

Documentation

newtype SetupFunc b a Source #

A function that can provide an a given a b.

You can think of this as a potentially-resource-aware version of 'b -> IO a'.

Constructors

SetupFunc 

Fields

Instances

Instances details
Monad (SetupFunc c) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

(>>=) :: SetupFunc c a -> (a -> SetupFunc c b) -> SetupFunc c b #

(>>) :: SetupFunc c a -> SetupFunc c b -> SetupFunc c b #

return :: a -> SetupFunc c a #

Functor (SetupFunc c) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

fmap :: (a -> b) -> SetupFunc c a -> SetupFunc c b #

(<$) :: a -> SetupFunc c b -> SetupFunc c a #

Applicative (SetupFunc c) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

pure :: a -> SetupFunc c a #

(<*>) :: SetupFunc c (a -> b) -> SetupFunc c a -> SetupFunc c b #

liftA2 :: (a -> b -> c0) -> SetupFunc c a -> SetupFunc c b -> SetupFunc c c0 #

(*>) :: SetupFunc c a -> SetupFunc c b -> SetupFunc c b #

(<*) :: SetupFunc c a -> SetupFunc c b -> SetupFunc c a #

MonadIO (SetupFunc c) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

liftIO :: IO a -> SetupFunc c a #

Category SetupFunc Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

id :: forall (a :: k). SetupFunc a a #

(.) :: forall (b :: k) (c :: k) (a :: k). SetupFunc b c -> SetupFunc a b -> SetupFunc a c #

makeSimpleSetupFunc :: (forall r. (a -> IO r) -> IO r) -> SetupFunc () a Source #

Turn a simple provider function into a SetupFunc.

This works together nicely with most supplier functions. Some examples:

useSimpleSetupFunc :: SetupFunc () a -> forall r. (a -> IO r) -> IO r Source #

Use a 'SetupFunc ()' as a simple provider function.

This is the opposite of the makeSimpleSetupFunc function

wrapSetupFunc :: (b -> SetupFunc () a) -> SetupFunc b a Source #

Wrap a function that produces a SetupFunc to into a SetupFunc.

This is useful to combine a given 'SetupFunc b' with other 'SetupFunc ()'s as follows:

mySetupFunc :: SetupFunc B A
mySetupFunc = wrapSetupFunc $ \b -> do
  r <- setupSomething
  c <- setupSomethingElse b r
  pure $ somehowCombine c r

setupSomething :: SetupFunc () R
setupSomething :: B -> R -> SetupFunc () C
somehowCombine :: C -> R -> A

unwrapSetupFunc :: SetupFunc b a -> b -> SetupFunc () a Source #

Unwrap a SetupFunc into a function that produces a SetupFunc

This is the opposite of wrapSetupFunc.

composeSetupFunc :: SetupFunc b a -> SetupFunc c b -> SetupFunc c a Source #

Compose two setup functions.

This is basically (.) but for SetupFuncs

connectSetupFunc :: SetupFunc c b -> SetupFunc b a -> SetupFunc c a Source #

Connect two setup functions.

This is basically 'flip (.)' but for SetupFuncs. It's exactly 'flip composeSetupFunc'.

setupAround :: SetupFunc () c -> TestDefM a c e -> TestDefM a () e Source #

Use around with a SetupFunc

setupAroundWith' :: HContains l a => (a -> SetupFunc d c) -> TestDefM l c e -> TestDefM l d e Source #