| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Control.Monad.Trans.Compose
Synopsis
- newtype ComposeT t1 t2 m a = ComposeT {
- deComposeT :: t1 (t2 m) a
- runComposeT :: (forall a. t1 (t2 m) a -> t2 m (StT t1 a)) -> (forall a. t2 m a -> m (StT t2 a)) -> forall a. ComposeT t1 t2 m a -> m (StT t2 (StT t1 a))
- runComposeT' :: (t1 (t2 m) a -> t2 m a) -> (t2 m a -> m a) -> ComposeT t1 t2 m a -> m a
ComposeT
ComposeT can be used in monad transformer stacks to derive instances.
This also allows the usage of these instances, while in the middle of the transformer stack. This proves particularly useful, when writing a runner for a transformer stack.
newtype ComposeT t1 t2 m a Source #
A newtype wrapper for two stacked monad transformers.
Access instances of the intermediate monad (t2 m), whenever t1 implements MonadTrans /
MonadTransControl / MonadTransControlIdentity.
Type level arguments:
Constructors
| ComposeT | |
Fields
| |
Instances
| (Monad (t2 m), Monoid w) => MonadRWS r w s (ComposeT (RWST r w s) t2 m) Source # | Set by |
Defined in Control.Monad.Trans.Compose | |
| (Monad (t2 m), Monoid w) => MonadRWS r w s (ComposeT (RWST r w s) t2 m) Source # | Set by |
Defined in Control.Monad.Trans.Compose | |
| (Monad (t1 (t2 m)), MonadTransControl t1, MonadRWS r w s (t2 m)) => MonadRWS r w s (ComposeT t1 t2 m) Source # | OVERLAPPABLE.
Elevated to |
Defined in Control.Monad.Trans.Compose | |
| (Monad (t1 (t2 m)), MonadTransControl (ComposeT t1 t2), MonadBaseControl b m) => MonadBaseControl b (ComposeT t1 t2 m) Source # | |
| (Monad (t1 (t2 m)), MonadTransControlIdentity (ComposeT t1 t2), MonadBaseControlIdentity b m) => MonadBaseControlIdentity b (ComposeT t1 t2 m) Source # | Elevated to |
Defined in Control.Monad.Trans.Compose Methods liftBaseWithIdentity :: ((forall x. ComposeT t1 t2 m x -> b x) -> b a) -> ComposeT t1 t2 m a # | |
| Monad (t2 m) => MonadError e (ComposeT (ExceptT e) t2 m) Source # | Set by |
Defined in Control.Monad.Trans.Compose | |
| (Monad (t1 (t2 m)), MonadTransControl t1, MonadError e (t2 m)) => MonadError e (ComposeT t1 t2 m) Source # | OVERLAPPABLE.
Elevated to |
Defined in Control.Monad.Trans.Compose Methods throwError :: e -> ComposeT t1 t2 m a # catchError :: ComposeT t1 t2 m a -> (e -> ComposeT t1 t2 m a) -> ComposeT t1 t2 m a # | |
| (Monad (t2 m), Monoid w) => MonadReader r (ComposeT (RWST r w s) t2 m) Source # | Set by |
| (Monad (t2 m), Monoid w) => MonadReader r (ComposeT (RWST r w s) t2 m) Source # | Set by |
| Monad (t2 m) => MonadReader r (ComposeT (ReaderT r) t2 m) Source # | Set by |
| (Monad (t1 (t2 m)), MonadTransControl t1, MonadReader r (t2 m)) => MonadReader r (ComposeT t1 t2 m) Source # | OVERLAPPABLE.
Elevated to |
| (Monad (t2 m), Monoid w) => MonadState s (ComposeT (RWST r w s) t2 m) Source # | Set by |
| (Monad (t2 m), Monoid w) => MonadState s (ComposeT (RWST r w s) t2 m) Source # | Set by |
| Monad (t2 m) => MonadState s (ComposeT (StateT s) t2 m) Source # | Set by |
| Monad (t2 m) => MonadState s (ComposeT (StateT s) t2 m) Source # | Set by |
| (Monad (t1 (t2 m)), MonadTrans t1, MonadState s (t2 m)) => MonadState s (ComposeT t1 t2 m) Source # | OVERLAPPABLE.
Elevated to |
| (Monad (t2 m), Monoid w) => MonadWriter w (ComposeT (RWST r w s) t2 m) Source # | Set by |
| (Monad (t2 m), Monoid w) => MonadWriter w (ComposeT (RWST r w s) t2 m) Source # | Set by |
| (Monad (t2 m), Monoid w) => MonadWriter w (ComposeT (WriterT w) t2 m) Source # | Set by |
| (Monad (t2 m), Monoid w) => MonadWriter w (ComposeT (WriterT w) t2 m) Source # | Set by |
| (Monad (t1 (t2 m)), MonadTransControl t1, MonadWriter w (t2 m)) => MonadWriter w (ComposeT t1 t2 m) Source # | OVERLAPPABLE.
Elevated to |
| (Monad (t1 (t2 m)), MonadTrans (ComposeT t1 t2), MonadBase b m) => MonadBase b (ComposeT t1 t2 m) Source # | Elevated to |
Defined in Control.Monad.Trans.Compose | |
| (forall (m :: Type -> Type). Monad m => Monad (t2 m), MonadTransControl t1, MonadTransControl t2) => MonadTransControl (ComposeT t1 t2) Source # | |
| (forall (m :: Type -> Type). Monad m => Monad (t2 m), MonadTransControlIdentity t1, MonadTransControlIdentity t2) => MonadTransControlIdentity (ComposeT t1 t2) Source # | |
Defined in Control.Monad.Trans.Compose Methods liftWithIdentity :: Monad m => ((forall x. ComposeT t1 t2 m x -> m x) -> m a) -> ComposeT t1 t2 m a # | |
| (forall (m :: Type -> Type). Monad m => Monad (t2 m), MonadTrans t1, MonadTrans t2) => MonadTrans (ComposeT t1 t2) Source # | |
Defined in Control.Monad.Trans.Compose | |
| (Monad (t1 (t2 m)), MonadTrans (ComposeT t1 t2), MonadIO m) => MonadIO (ComposeT t1 t2 m) Source # | Elevated to |
Defined in Control.Monad.Trans.Compose | |
| Applicative (t1 (t2 m)) => Applicative (ComposeT t1 t2 m) Source # | |
Defined in Control.Monad.Trans.Compose Methods pure :: a -> ComposeT t1 t2 m a # (<*>) :: ComposeT t1 t2 m (a -> b) -> ComposeT t1 t2 m a -> ComposeT t1 t2 m b # liftA2 :: (a -> b -> c) -> ComposeT t1 t2 m a -> ComposeT t1 t2 m b -> ComposeT t1 t2 m c # (*>) :: ComposeT t1 t2 m a -> ComposeT t1 t2 m b -> ComposeT t1 t2 m b # (<*) :: ComposeT t1 t2 m a -> ComposeT t1 t2 m b -> ComposeT t1 t2 m a # | |
| Functor (t1 (t2 m)) => Functor (ComposeT t1 t2 m) Source # | |
| Monad (t1 (t2 m)) => Monad (ComposeT t1 t2 m) Source # | |
| Monad (t2 m) => MonadCatch (ComposeT CatchT t2 m) Source # | Set by |
| (Monad (t1 (t2 m)), MonadTransControl t1, MonadCatch (t2 m)) => MonadCatch (ComposeT t1 t2 m) Source # | OVERLAPPABLE.
Elevated to |
| Monad (t2 m) => MonadThrow (ComposeT CatchT t2 m) Source # | Set by |
| (Monad (t1 (t2 m)), MonadTrans t1, MonadThrow (t2 m)) => MonadThrow (ComposeT t1 t2 m) Source # | OVERLAPPABLE.
Elevated to |
Defined in Control.Monad.Trans.Compose | |
| Monad (t2 m) => MonadCont (ComposeT (ContT r) t2 m) Source # | Set by |
| (Monad (t1 (t2 m)), MonadTransControl t1, MonadCont (t2 m)) => MonadCont (ComposeT t1 t2 m) Source # | OVERLAPPABLE.
Elevated to |
| (Monad (t1 (t2 m)), MonadTransControlIdentity (ComposeT t1 t2), MonadUnliftIO m) => MonadUnliftIO (ComposeT t1 t2 m) Source # | Elevated to |
Defined in Control.Monad.Trans.Compose | |
| type StT (ComposeT t1 t2) a Source # | |
Defined in Control.Monad.Trans.Compose | |
| type StM (ComposeT t1 t2 m) a Source # | Elevated to |
Run ComposeT
You have to run the composed monad transformers to get back into the base monad at some point.
Arguments
| :: (forall a. t1 (t2 m) a -> t2 m (StT t1 a)) | run |
| -> (forall a. t2 m a -> m (StT t2 a)) | run |
| -> forall a. ComposeT t1 t2 m a -> m (StT t2 (StT t1 a)) |
Run two stacked monad transformers.
This function takes the two individual monad transformer runners as arguments.
Arguments
| :: (t1 (t2 m) a -> t2 m a) | run |
| -> (t2 m a -> m a) | run |
| -> ComposeT t1 t2 m a -> m a |
Equivalent to runComposeT, but discards the monadic state StT.
This is a simple approach when your monad transformer stack doesn't carry monadic state.
StT(ComposeTt1 t2) a ~ a
This can be used to improve error messages when modifying a monad transformer stack.
Examples
Example 1: Create a new type class
When creating a new type class that supports ComposeT, you want to add recursive instances for
ComposeT.
class Monad m => MonadCustom m where
simpleMethod :: a -> m a
complicatedMethod :: (a -> m a) -> m a
You can easily derive those instances, after implementing an instance for Elevator.
This is explained in Control.Monad.Trans.Elevator.
Then it's possible to derive the recursive instance. This is an OVERLAPPABLE instance, because we want to be able to add new "base-case" instances through transformers in a stack.
deriving viaElevatort1 (t2 (m :: * -> *)) instance {-# OVERLAPPABLE #-} (Monad(t1 (t2 m)) ,MonadTransControlt1 , MonadCustom (t2 m) ) => MonadCustom (ComposeTt1 t2 m)
Example 2: Add an instance
Add a type class instance for a new monad transformer, when there already is a recursive instance
for ComposeT.
newtype CustomT m a = CustomT { unCustomT :: IdentityT m a }
deriving newtype (Functor, Applicative, Monad)
deriving newtype (MonadTrans, MonadTransControl, MonadTransControlIdentity)
First we need the regular instance.
The method implementations are undefined here, because they would only distract from
ComposeT.
instanceMonadm => MonadCustom (CustomT m) where simpleMethod =undefinedcomplicatedMethod =undefined
To add a "base-case" instance, that takes priority over the recursive instance, FlexibleInstances are required.
deriving via CustomT (t2 (m :: * -> *)) instanceMonad(t2 m) => MonadCustom (ComposeTCustomT t2 m)
Example 3: Build a transformer stack
Create a monad transformer stack and wrap it using a newtype.
type AppStackT =TransparentT.|>ReaderTBool.|>CustomT.|>ReaderTChar.|>StateTIntnewtype AppT m a = AppT { unAppT :: AppStackT m a } deriving newtype (Functor,Applicative,Monad)
Using .|> we can write AppStackT in the order of initialization.
We are adding TransparentT to the bottom of the stack,
so that all the other transformer instances actually end up in the stack.
Now we can simply derive just the instances, that we want.
deriving newtype (MonadTrans,MonadTransControl) deriving newtype (MonadStateInt) deriving newtype MonadCustom
We can even access instances, that would have been shadowed in a regular transformer stack.
deriving newtype (MonadReaderBool)
Example 4: Run a transformer stack
This is the part, that actually contains your application logic.
Because of the setup with ComposeT, we won't have to worry about lifting during the
initialization.
With ..> we can use the order of initialization again.
runAppT :: AppT m a -> m (StTAppT a) runAppT appTma =runTransparentT./>(\ tma ->runReaderTtmaTrue)./>runCustomT./>runReaderT'./>runStateT' $ unAppT appTma where runReaderT' ::MonadReaderBoolm =>ReaderTCharm a -> m a runReaderT' tma = do bool <-asklet char = if bool then 'Y' else 'N'runReaderTtma char runStateT' ::MonadReaderCharm =>StateTIntm a -> m (a,Int) runStateT' tma = do char <-asklet num =fromEnumcharrunStateTtma num