May 2020
Individual monads capture specific computational effects, e.g.:
What if we need to combine effects of several monads together?
forward :: Double -> Turtle ()
forward dist = Turtle $ do
s <- get -- get current state
...
lift $ drawInWindow ... -- perform I/O
put s { ... } -- update state
newtype StateIO s a -- abstract
instance Monad (StateIO s)
-- also Functor, Applicative
-- accessing state
get :: StateIO s s
put :: s -> StateIO s ()
-- lifting an I/O operation
lift :: IO a -> StateIO s a
-- run from some initial state
runStateIO :: StateIO s a -> s -> IO (s,a)
Recall
State s a
≃ s -> (s, a)
Hence
StateIO s a
≃ s -> IO (s, a)
StateIO s a
is a function that:
Note that both IO and result may depend on the state.
The Monad
instance is straight-forward:
instance Monad (StateIO s) where
return x = StateIO (\s -> return (s, x))
m >>= k = StateIO (\s -> do
(s',x) <- runStateIO m s
runStateIO (k x) s')
Also instances for Functor
and Applicative
(omitted).
get :: StateIO s s
get = StateIO (\s -> return (s,s))
put :: s -> StateIO s ()
put s = StateIO (\_ -> return (s,()))
A monad transformer takes an underlying monad and gives a new monad with some “extra” effect on-top of the original ones.
Monad | Effect | Transformer |
---|---|---|
Maybe |
partitiality (optional results) | MaybeT |
Either |
errors (exceptional results) | ExceptT |
State |
reading and writing state | StateT |
Reader |
reading from enviroment | ReaderT |
Writer |
writing output (logging) | WriterT |
IO |
input/output, foreign-functions | N/A |
MaybeT IO a
combines optional results with input/output.
StateT Int IO a
combines state with input/output (same as StateIO Int
)
StateT Int Maybe a
combines state with optional results
MaybeT (State Int) a
combines optional results with state
NB: the stacking order matters!
newtype Identity a
= Identity {runIdentity :: a}
instance Monad Identity where
return = Identity
Identity x >>= k
= Identity (runIdentity $ k x)
Identity a
is isomorphic to a
The basic monads can be seen as transformers stacked on to the identity monad.
Examples:
Maybe a
is equivalent to MaybeT Identity a
State s a
is equivalent to StateT s Identity a
MaybeT
MaybeT m
adds optional failure to some monad m
m
is a monad then MaybeT m
is also a monadMaybeT m
computation gives back an m
computation producing an optional resultnewAccount :: IO (Maybe (String,String))
newAccount = do
uid <- getLine
if validUser uid then do
pwd <- getLine
if validPassword s
then return (Just (uid, pwd))
else return Nothing
else return Nothing
validUser :: String -> Bool
...
validPassword :: String -> Bool
...
Using MaybeT
to combine optional results with IO
.
newAccount :: MaybeT IO (String,String)
newAccount = do
uid <- lift getLine
guard (validUser uid) -- from MonadPlus
pwd <- lift getLine
guard (validPassword pwd)
return (uid,pwd)
NB: use lift
to run an action from the underlying monad (IO
).
MaybeT
Monad instanceMaybeT m
is a monad whenever m
is a monad.
instance Monad m => Monad (MaybeT m) where
return = MaybeT . return . Just
p >>= k = MaybeT $
do mv <- runMaybeT p
case mv of
Nothing -> return Nothing
Just v -> runMaybeT (k v)
Apart from wrapping and unwrapping the underlying monad, the operations behave the same as in the Maybe
instance.
MaybeT
MonadPlus instanceMaybeT m
is a monad with a plus whenever m
is a monad.
instance Monad m => MonadPlus (MaybeT m) where
mzero = MaybeT (return Nothing)
mplus p q = MaybeT $ do
v <- runMaybeT p
case v of
Nothing -> runMaybeT q
Just _ -> return v
Again this is the same as the Maybe
instance with extra wrapping/unwrapping for monad m
.
Lifting can applied in any monad transformer using the type class MonadTrans
:
t
is the monad transformer (e.g. MaybeT
)m
is the underlying monad (e.g. IO
)MaybeT
The instance for MaybeT
simply has to run the m
-action and wrap the result in a Just
.
ExceptT
Recall that the Either
type can be used to represent computations that may return exceptions.
data Either a b = Left a | Right b
instance Monad (Either e) where
return = Right
Left e >>= k = Left e
Right v >>= k = k v
Left
represents an error result (exception)Right
represents a valid resulte
is the type of exceptions (e.g. String
)ExceptT e m
adds exceptions of type e
to m
computationsExceptT
computation we get back an Either
value wrapped in the underlying monadWe can throw an error in an ExceptT
computation using throwError
.
This is overloaded for any MonadError
— so it works with both ExceptT
transformers and Either
.
StateT
Recall the type of state monad:
The type for state transformer:
newtype State s a = State (s -> (a,s))
instance Monad (State s) where
...
-- read the state
get :: State s s
get = State $ \s -> (s,s)
-- write the state
put :: s -> State s ()
put s = State $ \_ -> ((),s))
The state operations in Control.Monad.State
are overloaded using a type class:
get :: MonadState s m => m s
put :: MonadState s m => s -> m ()
modify :: MonadState s m => (s -> s) -> m ()
This allows using these operations on either State
or StateT
.
ReaderT
and WriterT
Reader
allows reading from an environmentWriter
allows appending to some outputnewtype Reader e a
newtype Writer w a
ask :: Reader e e -- fetch current environment
tell :: w -> Writer w () -- append output
newtype Reader e a
= Reader { runReader :: e -> a }
instance Monad (Reader e) where
return x = Reader $ \e -> x
Reader f >>= k = Reader $ \e ->
runReader (k (f e)) e
Behaves like read-only state: the environment e
is passed by >>=
unmodified
-- ask the value of the enviroment
ask :: Reader e e
ask = Reader id
-- modify the value of the environment locally
local :: (e -> e) -> Reader e a -> Reader e a
local f m = Reader $ \e -> runReader m (f e)
ask
gives the value in the environmentlocal
runs a sub-computation with a locally modified environmenta
with some output w
w
should be a monoid (examples: String
, [a]
)newtype Writer w a
= Writer { runWriter :: (a, w) }
instance Monoid w => Monad (Writer w) where
return x = Writer (x, mempty)
Writer (a, w) >>= k
= let (b, w') = runWriter (k a)
in Writer (b, w `mappend` w')
return
gives the empty output>>=
concatenates the output of sub-computationsnewtype ReaderT e m a =
ReaderT {runReaderT :: e -> m a}
newtype WriterT w m a =
WriterT {runWriterT :: m (a, w)}
Reader
or Writer
effects to monad m