deriving-trans-0.5.2.0: Derive instances for monad transformer stacks
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Trans.Compose.Stack

Description

This module gives an alternative interface to build and run monad transformer stacks.

Using this approach is supposed to improve error messages and reduce errors, such as forgetting to add TransparentT at the bottom of the stack.

Synopsis

StackT

StackT is a more ergonomic way to define a monad transformer stack.

type family StackT (ts :: Stack) = (t :: (Type -> Type) -> Type -> Type) | t -> ts where ... Source #

An isomorphism between a Stack and the corresponding monad transformer, which can be built using ComposeT.

An additional TransparentT will automatically be used at the bottom of the stack. You only have to worry about the semantically relevant transformers.

Equations

StackT NilT = TransparentT 
StackT (ts :.|> t) = ComposeT t (StackT ts) 

runStackT and RunStackT

Monad transformer stacks, that only consist of IdentityT and ReaderT, can be run with runStackT.

If your transformer stack contains monadic state StT, you will have to use runComposeT or ./>! You can still use StackT for the type definition.

runStackT :: RunStackT ts m a -> StackT ts m a -> m a Source #

Run a monad transformer stack.

This takes a RunStackT as an argument containing the individual runners.

runStackT can only be used for monad transformer stacks without monadic state StT.

data RunStackT :: Stack -> (Type -> Type) -> Type -> Type where Source #

A data type representing the runner function of a monad transformer stack.

This is basically a heterogeneous list of monad transformer runners.

RunStackT can only be used for monad transformer stacks without monadic state StT.

Constructors

RunNilT :: RunStackT NilT m a

run an empty monad transformer stack

(:..>) infixl 1

run the next monad transformer on a stack

Fields

Stack

Stack is used to define monad transformer stacks with StackT.

data Stack where Source #

A data kind representing a monad transformer stack.

This is basically a type-level list of monad transformers.

Constructors

NilT :: Stack

an empty monad transformer stack

(:.|>) infixl 1

add a monad transformer to a stack

Fields

Examples

Feel free to compare these examples to the ones in Control.Monad.Trans.Compose.

Example 1: Build a transformer stack

Apply the type family StackT to a type of kind Stack and generate a monad transformer stack built with ComposeT.

type AppStack = NilT :.|> ReaderT Bool :.|> CustomT :.|> ReaderT Char
newtype AppT m a = AppT { unAppT :: StackT AppStack m a }
  deriving newtype (Functor, Applicative, Monad)
  deriving newtype (MonadTrans, MonadTransControl, MonadTransControlIdentity)
  deriving newtype MonadCustom
  deriving newtype (MonadReader Bool)

Example 2: Run a transformer stack

Use runStackT and supply it with a RunStackT argument.

runAppT :: AppT m a -> m a
runAppT appTma = runStackT runAppStackT $ unAppT appTma
 where
  runAppStackT = RunNilT
    :..> (\ tma -> runReaderT tma True)
    :..> runCustomT
    :..> runReaderT'

  runReaderT' :: MonadReader Bool m => ReaderT Char m a -> m a
  runReaderT' tma = do
    bool <- ask
    let char = if bool then 'Y' else 'N'
    runReaderT tma char