Search code examples
haskellmonadsmonad-transformerscontinuations

How to create a monad using StateT, ContT, and ReaderT?


How do I create a monad which uses State, Cont, and Reader transformers? I would like to read an environment, and update/use state. However, I would also like to pause/interrupt the action. For example, if a condition is met, the state remains unchanged.

So far I have a monad using ReaderT and StateT, but I cannot work out how to include ContT:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Test where
-- monads
import   Data.Functor.Identity (Identity, runIdentity)
import   Control.Monad.State
import   Control.Monad.Reader
import   Control.Monad.Cont

-- reader environment
type In = Integer

-- cont: if true then pause, else continue 
type Pause = Bool

-- state environment:
newtype StateType = StateType { s :: Integer }

newtype M r = M {_unM :: ReaderT In (ContT Pause (StateT StateType Identity)) r}
  deriving ( Functor, Applicative, Monad
           , MonadReader In
           , MonadCont   Pause
           , MonadState  StateType
           )

-- run monadic action
runM :: In -> Pause -> StateType -> M r -> StateType
runM inp pause initial act
  = runIdentity             -- unwrap identity
  $ flip execStateT initial -- unwrap state
  $ flip runContT   pause   -- unwrap cont
  $ flip runReaderT inp     -- unwrap reader
  $ _unM act                -- unwrap action

This gives the error:

* Expected kind `* -> *', but `Pause' has kind `*'
* In the first argument of `MonadCont', namely `Pause'
  In the newtype declaration for `M'
  |
24|         , MonadCont  Pause
  |

Ok, but why does Pause need kind * -> *?... I'm drowning in types, in need of explanation. What form does Pause have to take, a function? How does ContT integrate? Ultimately, I plan to use Cont for a control structure.


Solution

  • Unlike MonadReader and MonadState, the MonadCont type class takes only one parameter. Since that parameter m must be a Monad, it must have kind * -> *.

    In your deriving clause, you want MonadCont, not MonadCont Pause.

    added in response to followup question:

    ContT is defined as:

    newtype ContT r m a = ContT { runContT :: (a -> m r) -> m r }
    

    Note that the r in your definition of newtype M r is passed as the final (a) parameter to ContT. Plugging in the variables, you have

    ContT Bool (State StateType) a = ContT { 
        runContT :: (a -> State StateType Bool) -> (State StateType Bool)
      }
    

    This provides a computational context in which you can manipulate the StateType, and use delimited continuations. Eventually, you will construct a ContT Bool (State StateType) Bool. Then you can run the continuation (with evalContT), and return to the simpler State StateType context. (In practice, you may unwrap all 3 of your monad transformers in the same part of your program.)