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

Test.Syd.Def.SetupFunc

Description

The SetupFunc abstraction makes resource provider functions (of type (a -> IO r) -> IO r) composable.

Synopsis

Documentation

newtype SetupFunc old new Source #

A function that can provide an new given an old.

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

This type has a monad instance, which means you can now compose setup functions using regular do-notation.

Constructors

SetupFunc 

Fields

Instances

Instances details
Monad (SetupFunc old) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

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

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

return :: a -> SetupFunc old a #

Functor (SetupFunc old) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

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

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

Applicative (SetupFunc old) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

pure :: a -> SetupFunc old a #

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

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

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

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

MonadIO (SetupFunc old) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

liftIO :: IO a -> SetupFunc old 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 result. (resource -> IO result) -> IO result) -> SetupFunc () resource Source #

Turn a simple provider function into a SetupFunc.

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

useSimpleSetupFunc :: SetupFunc () resource -> forall result. (resource -> IO result) -> IO result Source #

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

This is the opposite of the makeSimpleSetupFunc function

wrapSetupFunc :: (old -> SetupFunc () new) -> SetupFunc old new 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 old new -> old -> SetupFunc () new Source #

Unwrap a SetupFunc into a function that produces a SetupFunc

This is the opposite of wrapSetupFunc.

composeSetupFunc :: SetupFunc newer newest -> SetupFunc old newer -> SetupFunc old newest Source #

Compose two setup functions.

This is (.) but for SetupFuncs

connectSetupFunc :: SetupFunc old newer -> SetupFunc newer newest -> SetupFunc old newest Source #

Connect two setup functions.

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

setupAround :: SetupFunc () inner -> TestDefM outers inner result -> TestDefM outers () result Source #

Use around with a SetupFunc

setupAroundWith :: SetupFunc oldInner newInner -> TestDefM outers newInner result -> TestDefM outers oldInner result Source #

setupAroundWith' :: HContains outers outer => (outer -> SetupFunc oldInner newInner) -> TestDefM outers newInner result -> TestDefM outers oldInner result Source #