Project 9: Monad Transformers from Scratch
Project 9: Monad Transformers from Scratch
Composing Effects: The Art of Stacking Monads
- Main Programming Language: Haskell
- Alternative Languages: Scala, PureScript
- Coolness Level: Level 4: Hardcore Tech Flex
- Difficulty: Level 4: Expert
- Knowledge Area: Effects / Monad Transformers
- Estimated Time: 3-4 weeks
- Prerequisites: Solid understanding of Functor, Applicative, Monad; experience with Maybe, Either, State, Reader, Writer monads individually
Learning Objectives
After completing this project, you will be able to:
- Explain why monads donât compose directly - Demonstrate why
Monad m => Monad n => Monad (m . n)doesnât hold in general - Implement common monad transformers from scratch - Build MaybeT, EitherT, ReaderT, StateT, WriterT without using mtl
- Understand the lift operation - Explain how
liftinjects base monad actions into the transformer stack - Implement the MonadTrans class - Define the type class and prove its laws
- Work with transformer stacks - Compose multiple transformers and understand the effect ordering
- Compare transformer ordering - Demonstrate how
StateT s (Either e)differs fromEitherT e (State s) - Implement MTL-style type classes - Create MonadReader, MonadState, MonadError for automatic lifting
Conceptual Foundation
The Problem: Monads Donât Compose
Youâve mastered individual monads:
Maybe a -- Computation that might fail
Either e a -- Computation that might fail with error info
Reader r a -- Computation that reads from environment
State s a -- Computation with mutable state
Writer w a -- Computation that logs output
IO a -- Computation with side effects
But real programs need multiple effects simultaneously:
-- Parse a config file (might fail)
-- Read environment variables (Reader)
-- Log parsing steps (Writer)
-- Update internal state (State)
-- Actually read the file (IO)
parseConfig :: ??? -- What type goes here?
The naive attempt fails:
-- Can we combine Maybe and State?
type MaybeState s a = Maybe (State s a)
-- Nope! This is Maybe applied to (State s a), not a new monad
-- We can't use (>>=) sensibly here
The fundamental problem: Given Monad m and Monad n, the composition m (n a) is NOT automatically a monad.
Why Monads Donât Compose: A Proof
For m (n a) to be a monad, we need:
join :: m (n (m (n a))) -> m (n a)
Letâs try to implement this:
join :: m (n (m (n a))) -> m (n a)
join mnmna = ???
-- We have: m (n (m (n a)))
-- We need: m (n a)
-- Using m's join: m (n (m (n a))) -> m (n (n a)) -- if we could join inner m
-- Using n's join: m (n (n a)) -> m (n a) -- if we could join inner n
-- But we can't use m's join on the inner layer!
-- We'd need to commute: n (m ...) -> m (n ...)
-- This is the PROBLEM
To join the inner m, weâd need to swap the order of m and n, but thereâs no general way to do this.
Specific counterexample:
-- Consider: IO (State s (IO (State s a)))
-- How do we combine the two IO layers? The two State layers?
-- The State layers have different states!
-- The IO layers represent different sequences of effects!
The Solution: Monad Transformers
A monad transformer is a type constructor T such that:
T mis a monad whenevermis a monad- Thereâs a way to âliftâ
mactions intoT m
class MonadTrans t where
lift :: Monad m => m a -> t m a
-- lift injects an action from the base monad into the transformer
Instead of composing arbitrary monads, we define transformers that know how to layer one specific effect onto any base monad.
The Core Insight: Wrapping and Unwrapping
Each transformer has a specific structure:
newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }
-- ^^^^^^ ^^^^^^^^^
-- Transformer Base monad wrapping Maybe
newtype StateT s m a = StateT { runStateT :: s -> m (a, s) }
-- ^^^^^^^^^^^^^^
-- State function returning in base monad
newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
-- ^^^^^^^
-- Reader function returning in base monad
The pattern: the transformerâs structure contains the base monad in a specific position.
MaybeT: The Simplest Transformer
Letâs build intuition with MaybeT:
newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }
What does this represent?
- An
mcomputation - That when run, produces a
Maybe a - Could be
Just value(success) orNothing(failure)
Example with IO:
MaybeT IO a ~ IO (Maybe a)
-- A computation that:
-- 1. Does some IO
-- 2. Might succeed (Just) or fail (Nothing)
lookupUser :: UserId -> MaybeT IO User
lookupUser uid = MaybeT $ do
result <- queryDatabase uid -- IO action
return result -- returns Maybe User
The Monad instance:
instance Monad m => Monad (MaybeT m) where
return a = MaybeT $ return (Just a)
(MaybeT mma) >>= f = MaybeT $ do
ma <- mma -- Run the m computation, get Maybe a
case ma of
Nothing -> return Nothing -- Propagate failure
Just a -> runMaybeT (f a) -- Continue with f
Visualizing the flow:
MaybeT computation 1 >>= function producing MaybeT computation 2
m (Maybe a) >>= (a -> MaybeT m b)
|
v
Run the m action, get Maybe a
|
v
+------+------+
| |
v v
Nothing Just a
| |
v v
return runMaybeT (f a)
Nothing |
| v
v m (Maybe b)
m (Maybe b)
|
v
m (Maybe b)
The MonadTrans Class
class MonadTrans t where
lift :: Monad m => m a -> t m a
Laws:
- Identity:
lift . return = return - Composition:
lift (m >>= f) = lift m >>= (lift . f)
These ensure that lifting preserves the monad structure.
Implementation for MaybeT:
instance MonadTrans MaybeT where
lift ma = MaybeT $ fmap Just ma
-- Run the m action, wrap result in Just
Visualization:
lift :: m a -> MaybeT m a
m a --> m (Maybe a)
via fmap Just
m a
|
v
ma >>= \a -> return (Just a)
|
v
m (Just a)
|
v
MaybeT (m (Just a))
StateT: Adding State to Any Monad
newtype StateT s m a = StateT { runStateT :: s -> m (a, s) }
What does this represent?
- A function from state
s - To an
mcomputation - That produces a value
aand new states
Compare with plain State:
newtype State s a = State { runState :: s -> (a, s) }
newtype StateT s m a = StateT { runStateT :: s -> m (a, s) }
-- ^
-- Added m wrapper!
The Monad instance:
instance Monad m => Monad (StateT s m) where
return a = StateT $ \s -> return (a, s)
(StateT smsa) >>= f = StateT $ \s -> do
(a, s') <- smsa s -- Run first, get value and new state
runStateT (f a) s' -- Run second with new state
Visualization:
StateT computation 1 >>= function producing StateT computation 2
(s -> m (a, s)) >>= (a -> StateT s m b)
Given initial state s:
|
v
Run smsa s in monad m
|
v
Get (a, s') in m
|
v
Apply f to a, get StateT s m b
|
v
Run (f a) with state s'
|
v
Get (b, s'') in m
|
v
Return m (b, s'')
ReaderT: Environment Access in Any Monad
newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
What does this represent?
- A function from environment
r - To an
mcomputation - That produces a value
a
ReaderT is special: itâs the simplest transformer because the environment is just passed through.
The Monad instance:
instance Monad m => Monad (ReaderT r m) where
return a = ReaderT $ \_ -> return a
(ReaderT rma) >>= f = ReaderT $ \r -> do
a <- rma r -- Run with environment
runReaderT (f a) r -- Pass SAME environment to continuation
Key insight: The environment r is threaded through but never modified.
WriterT: Logging in Any Monad
newtype WriterT w m a = WriterT { runWriterT :: m (a, w) }
What does this represent?
- An
mcomputation - That produces a value
aand accumulated logw
The Monad instance:
instance (Monoid w, Monad m) => Monad (WriterT w m) where
return a = WriterT $ return (a, mempty)
(WriterT maw) >>= f = WriterT $ do
(a, w1) <- maw -- Run first, get value and log
(b, w2) <- runWriterT (f a) -- Run second
return (b, w1 <> w2) -- Combine logs
Note: We need Monoid w to combine logs with <> and mempty.
EitherT (ExceptT): Errors with Information
newtype EitherT e m a = EitherT { runEitherT :: m (Either e a) }
Also called ExceptT in modern Haskell.
The Monad instance:
instance Monad m => Monad (EitherT e m) where
return a = EitherT $ return (Right a)
(EitherT mea) >>= f = EitherT $ do
ea <- mea
case ea of
Left e -> return (Left e) -- Propagate error
Right a -> runEitherT (f a) -- Continue
Stacking Transformers
Hereâs where it gets interesting. We can stack multiple transformers:
type App = ReaderT Config (StateT AppState (EitherT AppError IO))
-- Unwrapping:
-- ReaderT Config (...)
-- ^ Adds: environment access
--
-- StateT AppState (...)
-- ^ Adds: mutable state
--
-- EitherT AppError (...)
-- ^ Adds: error handling
--
-- IO
-- ^ Base: actual I/O
To run this stack, we peel off layers:
runApp :: App a -> Config -> AppState -> IO (Either AppError (a, AppState))
runApp app config state =
runEitherT $ -- IO (Either AppError (a, AppState))
runStateT -- EitherT AppError IO (a, AppState)
(runReaderT app config) -- StateT AppState (EitherT AppError IO) a
state
The Order Matters!
StateT s (Either e) vs EitherT e (State s):
-- StateT s (Either e) a = s -> Either e (a, s)
-- "Run with state, might fail, if succeeds gives new state"
-- EitherT e (State s) a = State s (Either e a) = s -> (Either e a, s)
-- "Run with state, always gives new state, might fail in value"
The difference:
-- StateT s (Either e): On failure, NO state change (state is inside Either)
example1 :: StateT Int (Either String) ()
example1 = do
modify (+1)
lift (Left "error") -- State change is LOST
modify (+1)
-- runStateT example1 0 = Left "error" (state was 1 but we don't see it)
-- EitherT e (State s): On failure, state changes are PRESERVED
example2 :: EitherT String (State Int) ()
example2 = do
lift (modify (+1))
throwError "error" -- State change is KEPT
lift (modify (+1))
-- runState (runEitherT example2) 0 = (Left "error", 1) (state is 1)
Visualization:
StateT s (Either e) a:
Initial state: s0
|
v
[computation 1] -> s1
|
v
[failure!] -----> Either is Left, entire state computation returns Left
| State s1 is LOST, we only know we failed
v
No final state
EitherT e (State s) a:
Initial state: s0
|
v
[computation 1] -> s1
|
v
[failure!] -> State still updates to s1, Either becomes Left
|
v
Final state: s1, Result: Left e
Lifting Through the Stack
When stacking transformers, we need to lift operations from inner layers:
type Stack = ReaderT Config (StateT AppState IO)
-- Using Reader (outermost):
askConfig :: Stack Config
askConfig = ask -- No lift needed
-- Using State (one layer in):
getState :: Stack AppState
getState = lift get -- One lift
-- Using IO (base):
doIO :: IO a -> Stack a
doIO = lift . lift -- Two lifts
The pattern: Each transformer layer requires one lift.
MTL-Style Type Classes
The explicit lifting becomes tedious. MTL (Monad Transformer Library) provides type classes:
class Monad m => MonadReader r m | m -> r where
ask :: m r
local :: (r -> r) -> m a -> m a
class Monad m => MonadState s m | m -> s where
get :: m s
put :: s -> m ()
class Monad m => MonadError e m | m -> e where
throwError :: e -> m a
catchError :: m a -> (e -> m a) -> m a
Now we write constraints instead of explicit lifts:
-- Instead of:
myFunction :: ReaderT Config (StateT AppState IO) Result
myFunction = do
config <- ask
state <- lift get
result <- lift $ lift $ someIO
...
-- We write:
myFunction :: (MonadReader Config m, MonadState AppState m, MonadIO m)
=> m Result
myFunction = do
config <- ask -- MonadReader provides ask
state <- get -- MonadState provides get
result <- liftIO someIO -- MonadIO provides liftIO
...
Benefits:
- No manual counting of lifts
- Functions work with ANY stack that provides the effects
- Easy to change the stack later
Implementing MTL-Style Instances
For each transformer, we implement the relevant type classes:
-- ReaderT is the "canonical" MonadReader
instance Monad m => MonadReader r (ReaderT r m) where
ask = ReaderT return
local f (ReaderT rma) = ReaderT (rma . f)
-- ReaderT passes through other effects
instance MonadState s m => MonadState s (ReaderT r m) where
get = lift get
put = lift . put
instance MonadError e m => MonadError e (ReaderT r m) where
throwError = lift . throwError
catchError (ReaderT rma) handler = ReaderT $ \r ->
catchError (rma r) (\e -> runReaderT (handler e) r)
The n^2 Instance Problem
With MTL-style, for n transformers and n type classes, we need approximately n^2 instances:
MonadReader MonadState MonadError MonadWriter
ReaderT canonical pass-thru pass-thru pass-thru
StateT pass-thru canonical pass-thru pass-thru
EitherT pass-thru pass-thru canonical pass-thru
WriterT pass-thru pass-thru pass-thru canonical
This is a known limitation. Solutions include:
- Code generation
- Effect systems (like polysemy, fused-effects)
- More general transformers (like
Eff)
Practical Patterns
1. The ReaderT IO Pattern
Many applications use this minimal stack:
newtype App a = App { unApp :: ReaderT AppEnv IO a }
deriving (Functor, Applicative, Monad, MonadIO, MonadReader AppEnv)
data AppEnv = AppEnv
{ envConfig :: Config
, envDatabase :: Connection
, envLogger :: Logger
}
runApp :: AppEnv -> App a -> IO a
runApp env (App m) = runReaderT m env
State is handled explicitly (STM, IORef), errors with exceptions.
2. ExceptT for Pure Error Handling
type PureComputation = ExceptT ValidationError (State FormData) Result
validate :: PureComputation
validate = do
data <- lift get
when (null $ dataName data) $
throwError (ValidationError "Name required")
when (dataAge data < 0) $
throwError (ValidationError "Invalid age")
return (processData data)
3. Monad Stacks in Production
Servant (web framework):
type AppM = ReaderT AppEnv (ExceptT ServantErr IO)
Yesod (web framework):
type Handler = HandlerFor App
-- Internally similar to ReaderT with state and errors
The Laws of MonadTrans
The MonadTrans laws ensure lift behaves sensibly:
Law 1: Identity
lift . return = return
-- Lifting a pure value is the same as pure in the transformer
Law 2: Composition
lift (m >>= f) = lift m >>= (lift . f)
-- Lifting a sequence is the same as sequencing lifts
Verification for MaybeT:
-- Law 1:
lift (return a)
= MaybeT $ fmap Just (return a)
= MaybeT $ return (Just a)
= return a -- by MaybeT's return
-- Law 2:
lift (m >>= f)
= MaybeT $ fmap Just (m >>= f)
= MaybeT $ (fmap Just m >>= \a -> fmap Just (f a)) -- fmap/>>= interaction
-- ... (tedious but verifiable)
= lift m >>= (lift . f)
ContT: The Mind-Bending Transformer
The continuation monad transformer is special:
newtype ContT r m a = ContT { runContT :: (a -> m r) -> m r }
What does this represent?
- Given a continuation
(a -> m r) - Produces the final result
m r - Can invoke the continuation zero, one, or many times!
The Monad instance:
instance Monad (ContT r m) where -- Note: no constraint on m!
return a = ContT $ \k -> k a
(ContT c) >>= f = ContT $ \k ->
c (\a -> runContT (f a) k)
Mind-bending property: ContT r m is a monad for ANY type constructor m, not just monads!
This is because continuations internalize the control flow.
The Identity Monad and Identity Transformer
newtype Identity a = Identity { runIdentity :: a }
newtype IdentityT m a = IdentityT { runIdentityT :: m a }
These are useful for:
- Instantiating transformers with no base effect
- Testing transformers in isolation
-- State is just StateT over Identity
type State s = StateT s Identity
-- Reader is just ReaderT over Identity
type Reader r = ReaderT r Identity
Performance Considerations
Transformer stacks have overhead:
- Wrapping/unwrapping: Each layer adds indirection
- Dictionary passing: MTL-style uses type class dictionaries
- Inline opportunities: GHC can often inline away overhead
Optimization tips:
-- Use SPECIALIZE pragmas
{-# SPECIALIZE myFunc :: ReaderT Config (StateT AppState IO) Result #-}
-- Avoid polymorphism in hot paths
concreteFunc :: ReaderT Config (StateT AppState IO) Result
concreteFunc = ... -- GHC can optimize this better
-- Consider CPS-based libraries for performance
-- (streaming, conduit, pipes handle effects differently)
Alternatives to Transformers
The transformer approach has drawbacks:
- n^2 instances
- Fixed stack order
- Performance overhead
Alternatives:
1. Free Monads / Freer Monads
-- Define effects as data types
data Console a where
PutLine :: String -> Console ()
GetLine :: Console String
-- Interpret later
runConsoleIO :: Eff '[Console] a -> IO a
2. Algebraic Effect Systems
-- polysemy, fused-effects
myProgram :: Members '[Reader Config, State AppState, Error AppError] r
=> Sem r Result
3. Capability-Based Design
-- Pass explicit capabilities
myProgram :: HasReader Config m => HasState AppState m => m Result
Project Specification
Core Requirements
Implement a monad transformer library from scratch:
1. Basic Transformers
MaybeT- Optional failureEitherT(orExceptT) - Errors with informationReaderT- Environment accessStateT- Mutable stateWriterT- Log accumulation
2. Type Class Instances
For each transformer, implement:
FunctorApplicativeMonadMonadTrans
3. Run Functions
runMaybeT :: MaybeT m a -> m (Maybe a)
runEitherT :: EitherT e m a -> m (Either e a)
runReaderT :: ReaderT r m a -> r -> m a
runStateT :: StateT s m a -> s -> m (a, s)
runWriterT :: WriterT w m a -> m (a, w)
4. MTL-Style Type Classes
class MonadReader r m | m -> r where
ask :: m r
local :: (r -> r) -> m a -> m a
class MonadState s m | m -> s where
get :: m s
put :: s -> m ()
modify :: (s -> s) -> m ()
class MonadError e m | m -> e where
throwError :: e -> m a
catchError :: m a -> (e -> m a) -> m a
class Monoid w => MonadWriter w m | m -> w where
tell :: w -> m ()
listen :: m a -> m (a, w)
pass :: m (a, w -> w) -> m a
5. Pass-Through Instances
Each transformer should pass through other effects:
-- ReaderT passes through State, Error, Writer
-- StateT passes through Reader, Error, Writer
-- etc.
6. Demonstration Program
Build a program using a multi-layer stack:
type App = ReaderT Config (StateT AppState (EitherT AppError IO))
-- Demonstrate:
-- 1. Reading config
-- 2. Updating state
-- 3. Handling errors
-- 4. Performing IO
Stretch Goals
- Implement
ContT(continuation transformer) - Implement
RWST(Reader-Writer-State combined) - Add
MonadIOclass and instances - Verify transformer laws with QuickCheck
- Benchmark against mtl library
Solution Architecture
Module Structure
src/
Control/
Monad/
Trans/
Class.hs -- MonadTrans class
Maybe.hs -- MaybeT
Either.hs -- EitherT
Reader.hs -- ReaderT
State.hs -- StateT
Writer.hs -- WriterT
Identity.hs -- IdentityT
Class/
Reader.hs -- MonadReader
State.hs -- MonadState
Error.hs -- MonadError
Writer.hs -- MonadWriter
Examples/
Stack.hs -- Multi-transformer example
OrderMatters.hs -- Demonstrate effect ordering
test/
Laws/
Monad.hs -- Monad law tests
Trans.hs -- MonadTrans law tests
Integration/
StackSpec.hs -- Integration tests
Core Type Definitions
-- Control/Monad/Trans/Class.hs
class MonadTrans t where
lift :: Monad m => m a -> t m a
-- Control/Monad/Trans/Maybe.hs
newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }
-- Control/Monad/Trans/Either.hs
newtype EitherT e m a = EitherT { runEitherT :: m (Either e a) }
-- Control/Monad/Trans/Reader.hs
newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
-- Control/Monad/Trans/State.hs
newtype StateT s m a = StateT { runStateT :: s -> m (a, s) }
-- Control/Monad/Trans/Writer.hs
newtype WriterT w m a = WriterT { runWriterT :: m (a, w) }
Implementation Guide
Phase 1: MaybeT
Start with the simplest transformer.
module Control.Monad.Trans.Maybe where
newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }
instance Functor m => Functor (MaybeT m) where
fmap f (MaybeT mma) = MaybeT $ fmap (fmap f) mma
-- Outer fmap: into m
-- Inner fmap: into Maybe
instance Monad m => Applicative (MaybeT m) where
pure = MaybeT . return . Just
MaybeT mf <*> MaybeT ma = MaybeT $ do
maybeF <- mf
case maybeF of
Nothing -> return Nothing
Just f -> do
maybeA <- ma
return (fmap f maybeA)
instance Monad m => Monad (MaybeT m) where
return = pure
MaybeT mma >>= f = MaybeT $ do
ma <- mma
case ma of
Nothing -> return Nothing
Just a -> runMaybeT (f a)
instance MonadTrans MaybeT where
lift = MaybeT . fmap Just
-- Convenience function
nothing :: Monad m => MaybeT m a
nothing = MaybeT $ return Nothing
Test it:
example :: MaybeT IO String
example = do
lift $ putStrLn "Enter name (empty to fail):"
name <- lift getLine
if null name
then nothing
else return ("Hello, " ++ name)
-- runMaybeT example
-- Enter name:
-- > Alice
-- Just "Hello, Alice"
Phase 2: EitherT
Similar to MaybeT but with error information.
module Control.Monad.Trans.Either where
newtype EitherT e m a = EitherT { runEitherT :: m (Either e a) }
instance Functor m => Functor (EitherT e m) where
fmap f (EitherT mea) = EitherT $ fmap (fmap f) mea
instance Monad m => Applicative (EitherT e m) where
pure = EitherT . return . Right
EitherT mef <*> EitherT mea = EitherT $ do
ef <- mef
case ef of
Left e -> return (Left e)
Right f -> do
ea <- mea
return (fmap f ea)
instance Monad m => Monad (EitherT e m) where
return = pure
EitherT mea >>= f = EitherT $ do
ea <- mea
case ea of
Left e -> return (Left e)
Right a -> runEitherT (f a)
instance MonadTrans (EitherT e) where
lift = EitherT . fmap Right
-- Error operations
throwE :: Monad m => e -> EitherT e m a
throwE = EitherT . return . Left
catchE :: Monad m => EitherT e m a -> (e -> EitherT e' m a) -> EitherT e' m a
catchE (EitherT mea) handler = EitherT $ do
ea <- mea
case ea of
Left e -> runEitherT (handler e)
Right a -> return (Right a)
Phase 3: ReaderT
The environment-passing transformer.
module Control.Monad.Trans.Reader where
newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
instance Functor m => Functor (ReaderT r m) where
fmap f (ReaderT rma) = ReaderT $ \r -> fmap f (rma r)
instance Applicative m => Applicative (ReaderT r m) where
pure a = ReaderT $ \_ -> pure a
ReaderT rmf <*> ReaderT rma = ReaderT $ \r ->
rmf r <*> rma r
instance Monad m => Monad (ReaderT r m) where
return = pure
ReaderT rma >>= f = ReaderT $ \r -> do
a <- rma r
runReaderT (f a) r
instance MonadTrans (ReaderT r) where
lift ma = ReaderT $ \_ -> ma
-- Reader operations
ask :: Monad m => ReaderT r m r
ask = ReaderT return
asks :: Monad m => (r -> a) -> ReaderT r m a
asks f = ReaderT $ \r -> return (f r)
local :: (r -> r) -> ReaderT r m a -> ReaderT r m a
local f (ReaderT rma) = ReaderT $ \r -> rma (f r)
Phase 4: StateT
The state-threading transformer.
module Control.Monad.Trans.State where
newtype StateT s m a = StateT { runStateT :: s -> m (a, s) }
instance Functor m => Functor (StateT s m) where
fmap f (StateT smas) = StateT $ \s ->
fmap (\(a, s') -> (f a, s')) (smas s)
instance Monad m => Applicative (StateT s m) where
pure a = StateT $ \s -> return (a, s)
StateT smfs <*> StateT smas = StateT $ \s -> do
(f, s') <- smfs s
(a, s'') <- smas s'
return (f a, s'')
instance Monad m => Monad (StateT s m) where
return = pure
StateT smas >>= f = StateT $ \s -> do
(a, s') <- smas s
runStateT (f a) s'
instance MonadTrans (StateT s) where
lift ma = StateT $ \s -> do
a <- ma
return (a, s)
-- State operations
get :: Monad m => StateT s m s
get = StateT $ \s -> return (s, s)
put :: Monad m => s -> StateT s m ()
put s = StateT $ \_ -> return ((), s)
modify :: Monad m => (s -> s) -> StateT s m ()
modify f = StateT $ \s -> return ((), f s)
gets :: Monad m => (s -> a) -> StateT s m a
gets f = StateT $ \s -> return (f s, s)
-- Evaluation variants
evalStateT :: Monad m => StateT s m a -> s -> m a
evalStateT m s = fmap fst (runStateT m s)
execStateT :: Monad m => StateT s m a -> s -> m s
execStateT m s = fmap snd (runStateT m s)
Phase 5: WriterT
The log-accumulating transformer.
module Control.Monad.Trans.Writer where
import Data.Monoid
newtype WriterT w m a = WriterT { runWriterT :: m (a, w) }
instance Functor m => Functor (WriterT w m) where
fmap f (WriterT maw) = WriterT $ fmap (\(a, w) -> (f a, w)) maw
instance (Monoid w, Applicative m) => Applicative (WriterT w m) where
pure a = WriterT $ pure (a, mempty)
WriterT mfw <*> WriterT maw = WriterT $
liftA2 (\(f, w1) (a, w2) -> (f a, w1 <> w2)) mfw maw
instance (Monoid w, Monad m) => Monad (WriterT w m) where
return = pure
WriterT maw >>= f = WriterT $ do
(a, w1) <- maw
(b, w2) <- runWriterT (f a)
return (b, w1 <> w2)
instance Monoid w => MonadTrans (WriterT w) where
lift ma = WriterT $ do
a <- ma
return (a, mempty)
-- Writer operations
tell :: (Monoid w, Monad m) => w -> WriterT w m ()
tell w = WriterT $ return ((), w)
listen :: Monad m => WriterT w m a -> WriterT w m (a, w)
listen (WriterT maw) = WriterT $ do
(a, w) <- maw
return ((a, w), w)
pass :: Monad m => WriterT w m (a, w -> w) -> WriterT w m a
pass (WriterT mawf) = WriterT $ do
((a, f), w) <- mawf
return (a, f w)
Phase 6: MTL-Style Type Classes
module Control.Monad.Class.Reader where
import Control.Monad.Trans.Class
import Control.Monad.Trans.Reader (ReaderT(..))
import Control.Monad.Trans.State (StateT(..))
import Control.Monad.Trans.Writer (WriterT(..))
import Control.Monad.Trans.Maybe (MaybeT(..))
class Monad m => MonadReader r m | m -> r where
ask :: m r
local :: (r -> r) -> m a -> m a
-- Canonical instance
instance Monad m => MonadReader r (ReaderT r m) where
ask = ReaderT return
local f (ReaderT rma) = ReaderT $ \r -> rma (f r)
-- Pass-through instances
instance MonadReader r m => MonadReader r (StateT s m) where
ask = lift ask
local f (StateT smas) = StateT $ \s -> local f (smas s)
instance MonadReader r m => MonadReader r (MaybeT m) where
ask = lift ask
local f (MaybeT mma) = MaybeT $ local f mma
instance (Monoid w, MonadReader r m) => MonadReader r (WriterT w m) where
ask = lift ask
local f (WriterT maw) = WriterT $ local f maw
module Control.Monad.Class.State where
class Monad m => MonadState s m | m -> s where
get :: m s
put :: s -> m ()
modify :: MonadState s m => (s -> s) -> m ()
modify f = do
s <- get
put (f s)
gets :: MonadState s m => (s -> a) -> m a
gets f = fmap f get
-- Canonical instance
instance Monad m => MonadState s (StateT s m) where
get = StateT $ \s -> return (s, s)
put s = StateT $ \_ -> return ((), s)
-- Pass-through instances
instance MonadState s m => MonadState s (ReaderT r m) where
get = lift get
put = lift . put
instance MonadState s m => MonadState s (MaybeT m) where
get = lift get
put = lift . put
-- Note: WriterT also needs pass-through, etc.
Phase 7: Demonstration Program
module Examples.Stack where
import Control.Monad.Trans.Class
import Control.Monad.Trans.Reader
import Control.Monad.Trans.State
import Control.Monad.Trans.Either
import Control.Monad.Class.Reader
import Control.Monad.Class.State
-- Configuration
data Config = Config
{ configMaxItems :: Int
, configDebug :: Bool
}
-- Application state
data AppState = AppState
{ stateItems :: [String]
, stateCount :: Int
}
-- Errors
data AppError
= TooManyItems
| EmptyName
deriving (Show, Eq)
-- The stack
type App = ReaderT Config (StateT AppState (EitherT AppError IO))
-- Run the stack
runApp :: Config -> AppState -> App a -> IO (Either AppError (a, AppState))
runApp config state app =
runEitherT $ runStateT (runReaderT app config) state
-- Example operations
addItem :: String -> App ()
addItem name = do
when (null name) $
lift $ lift $ throwE EmptyName
maxItems <- asks configMaxItems
currentCount <- gets stateCount
when (currentCount >= maxItems) $
lift $ lift $ throwE TooManyItems
debug <- asks configDebug
when debug $
lift $ lift $ lift $ putStrLn $ "Adding item: " ++ name
modify $ \s -> s
{ stateItems = name : stateItems s
, stateCount = stateCount s + 1
}
listItems :: App [String]
listItems = do
items <- gets stateItems
debug <- asks configDebug
when debug $
lift $ lift $ lift $ putStrLn $ "Listing " ++ show (length items) ++ " items"
return items
-- Example usage
example :: App [String]
example = do
addItem "First"
addItem "Second"
addItem "Third"
listItems
main :: IO ()
main = do
let config = Config { configMaxItems = 5, configDebug = True }
let state = AppState { stateItems = [], stateCount = 0 }
result <- runApp config state example
case result of
Left err -> putStrLn $ "Error: " ++ show err
Right (items, finalState) -> do
putStrLn $ "Items: " ++ show items
putStrLn $ "Final count: " ++ show (stateCount finalState)
Testing Strategy
Unit Tests
-- Test MaybeT Monad laws
describe "MaybeT" $ do
it "obeys left identity" $ do
let k x = MaybeT $ return $ Just (x + 1)
runMaybeT (return 5 >>= k) `shouldBe` runMaybeT (k 5)
it "obeys right identity" $ do
let m = MaybeT $ return $ Just 5
runMaybeT (m >>= return) `shouldBe` runMaybeT m
it "obeys associativity" $ do
let m = MaybeT $ return $ Just 5
let k x = MaybeT $ return $ Just (x + 1)
let h x = MaybeT $ return $ Just (x * 2)
runMaybeT ((m >>= k) >>= h) `shouldBe` runMaybeT (m >>= (\x -> k x >>= h))
-- Test MonadTrans laws
describe "MonadTrans" $ do
describe "MaybeT" $ do
it "lift . return = return" $ do
let liftReturn :: Int -> MaybeT Identity Int
liftReturn = lift . return
runMaybeT (liftReturn 5) `shouldBe` runMaybeT (return 5)
it "lift (m >>= f) = lift m >>= (lift . f)" $ do
let m = Identity 5
let f x = Identity (x + 1)
runMaybeT (lift (m >>= f)) `shouldBe`
runMaybeT (lift m >>= (lift . f))
Property-Based Tests
prop_stateTPreservesState :: Int -> Int -> Property
prop_stateTPreservesState initial delta =
let action :: StateT Int Identity Int
action = do
modify (+ delta)
get
in runIdentity (runStateT action initial) === (initial + delta, initial + delta)
prop_readerTReadsEnvironment :: Int -> Property
prop_readerTReadsEnvironment env =
let action :: ReaderT Int Identity Int
action = ask
in runIdentity (runReaderT action env) === env
prop_writerTAccumulatesOutput :: [String] -> [String] -> Property
prop_writerTAccumulatesOutput w1 w2 =
let action :: WriterT [String] Identity ()
action = tell w1 >> tell w2
in runIdentity (runWriterT action) === ((), w1 ++ w2)
Integration Tests
describe "Transformer stacks" $ do
it "StateT over Either preserves state on success" $ do
let action = modify (+1) >> get
runEither (runStateT action 0) `shouldBe` Right (1, 1)
it "StateT over Either loses state on failure" $ do
let action = do
modify (+1)
lift (Left "error")
modify (+1)
runEither (runStateT action 0) `shouldBe` Left "error"
it "EitherT over State preserves state on failure" $ do
let action = do
lift (modify (+1))
throwE "error"
lift (modify (+1))
runState (runEitherT action) 0 `shouldBe` (Left "error", 1)
Common Pitfalls
Pitfall 1: Confusing Stack Order
Problem: Misunderstanding what the stack order means.
-- These are DIFFERENT:
type Stack1 = StateT s (Either e) -- s -> Either e (a, s)
type Stack2 = EitherT e (State s) -- s -> (Either e a, s)
Solution: Draw out the types and think about what happens on failure.
Pitfall 2: Forgetting to Lift
Problem: Using base monad operations without lifting.
-- WRONG: get is for StateT, not for the outer monad
bad :: ReaderT r (StateT s IO) s
bad = get -- Type error!
-- CORRECT:
good :: ReaderT r (StateT s IO) s
good = lift get
Solution: Use MTL-style type classes to avoid manual lifting.
Pitfall 3: Infinite Lifting
Problem: Losing track of how many lifts are needed.
type Deep = ReaderT r (StateT s (WriterT w (EitherT e IO)))
-- How many lifts for IO?
doIO :: IO a -> Deep a
doIO = lift . lift . lift . lift -- Easy to get wrong!
Solution: Use liftIO from MonadIO class, or define helper functions.
Pitfall 4: Wrong Monoid for WriterT
Problem: Using WriterT with a non-monoid or wrong monoid.
-- This won't compile without Monoid:
type Bad = WriterT Int IO a -- Int is not a Monoid by default
-- Use Sum or Product:
type Good = WriterT (Sum Int) IO a
Pitfall 5: Lazy WriterT Space Leaks
Problem: Lazy accumulation in WriterT causes space leaks.
-- Standard WriterT is lazy, accumulates thunks
action = do
tell (Sum 1)
tell (Sum 2)
-- ...millions of tells...
-- Creates huge thunk chain!
Solution: Use strict WriterT (Control.Monad.Trans.Writer.Strict) or CPS WriterT.
Extensions and Challenges
Extension 1: Implement ContT
The continuation transformer is powerful and mind-bending:
newtype ContT r m a = ContT { runContT :: (a -> m r) -> m r }
-- Challenge: Implement Functor, Applicative, Monad
-- Notice: No Monad constraint on m!
Extension 2: Implement RWST
Combined Reader-Writer-State transformer:
newtype RWST r w s m a = RWST { runRWST :: r -> s -> m (a, s, w) }
-- More efficient than stacking three separate transformers
Extension 3: Build a Free Monad Alternative
Implement effects without n^2 instances:
data Eff (effs :: [* -> *]) a where
Pure :: a -> Eff effs a
Impure :: Union effs a -> (a -> Eff effs b) -> Eff effs b
-- Effects are data types, interpretation is separate
Extension 4: Monad Morphisms
Implement natural transformations between monad stacks:
class MFunctor t where
hoist :: Monad m => (forall x. m x -> n x) -> t m a -> t n a
-- hoist changes the base monad
Extension 5: Selective Applicative
Explore the space between Applicative and Monad:
class Applicative f => Selective f where
select :: f (Either a b) -> f (a -> b) -> f b
-- More powerful than Applicative, weaker than Monad
-- Enables static analysis of effects
Real-World Connections
Production Use
- Servant: Uses
ReaderToverHandler(which isExceptToverIO) - Yesod: Custom monad stack for web handlers
- Persistent: Database operations in
ReaderT SqlBackend - Amazonka: AWS operations in
AWST(ReaderT-based)
When to Use Transformers
Good fit:
- Clear layering of effects
- Need to run/interpret effects differently
- Building a library with abstract effects
Consider alternatives when:
- Performance is critical (consider effect systems)
- Many effects interact (consider free monads)
- Simple application (ReaderT IO pattern may suffice)
The ReaderT IO Pattern
Many production Haskell apps use just:
newtype App a = App (ReaderT Env IO a)
data Env = Env
{ envConfig :: Config
, envLogger :: Logger
, envDatabase :: Pool Connection
, envState :: TVar AppState -- Mutable state via STM
}
State is handled with IORef/TVar/MVar, errors with exceptions. Simpler and often faster than full transformer stacks.
Interview Questions
- âWhy donât monads compose in general?â
- Canât define
join :: m (n (m (n a))) -> m (n a)without knowing how to commutemandn - Would need
swap :: n (m a) -> m (n a)which doesnât exist generically
- Canât define
- âWhat is the
liftoperation and what laws must it satisfy?âlift :: Monad m => m a -> t m ainjects base monad actions- Law 1:
lift . return = return - Law 2:
lift (m >>= f) = lift m >>= (lift . f)
- âHow does
StateT s (Either e) adiffer fromEitherT e (State s) a?â- First: On error, state changes are lost
- Second: State changes are preserved even on error
- Types:
s -> Either e (a, s)vss -> (Either e a, s)
- âWhat is the MTL style and what problem does it solve?â
- Type classes like
MonadReader,MonadStateabstract over stacks - Solves: manual lifting, fixed stack structure
- Problem: n^2 instances needed
- Type classes like
- âWhen would you use
ContT?â- When you need to capture continuations
- Early exit, coroutines, backtracking
- Making any type constructor into a monad
- âWhat is a monad morphism?â
- Natural transformation between monad stacks
hoist :: (forall x. m x -> n x) -> t m a -> t n a- Changes the base monad without changing the transformer
- âCompare transformers to free monads for effect handling.â
- Transformers: Fixed stack, efficient, n^2 instances
- Free monads: Flexible, interpretable, more overhead
- Each has trade-offs depending on use case
Self-Assessment Checklist
Core Understanding
- I can explain why monads donât compose generally
- I understand the structure of each transformer type
- I can derive the Monad instance for any transformer
- I know what
liftdoes and its laws
Implementation Skills
- I have implemented MaybeT from scratch
- I have implemented EitherT from scratch
- I have implemented ReaderT from scratch
- I have implemented StateT from scratch
- I have implemented WriterT from scratch
Stacking Skills
- I can build and run multi-layer transformer stacks
- I understand how effect ordering matters
- I can draw the expanded types for transformer stacks
- I know when to use which transformer
MTL Style
- I have implemented MonadReader class and instances
- I have implemented MonadState class and instances
- I understand the n^2 instance problem
- I can use MTL-style constraints in my code
Advanced Topics
- I understand ContT and its special properties
- I know about alternatives (free monads, effect systems)
- I can make informed decisions about when to use transformers
- I understand the ReaderT IO pattern
Resources
Books
| Book | Chapter | What Youâll Learn |
|---|---|---|
| âHaskell in Depthâ (Bragilevsky) | Chapter 5 | Monad transformers in detail |
| âHaskell Programming from First Principlesâ | Chapter 26 | Transformers step by step |
| âReal World Haskellâ | Chapter 18 | Monad transformers introduction |
| âThinking with Typesâ (Sandy Maguire) | Chapters on GADTs/effects | Advanced effect systems |
Papers
- âMonad Transformers Step by Stepâ by Martin Grabmuller
- Excellent tutorial building up transformers incrementally
- âMonad Transformers and Modular Interpretersâ by Sheng Liang, Paul Hudak, Mark Jones
- Foundational paper on transformer semantics
- âExtensible Effectsâ by Oleg Kiselyov et al.
- Alternative to transformers avoiding n^2 problem
Online Resources
- Haskell Wiki: Monad Transformers
- Monday Morning Haskell: Monad Transformers
- FP Complete: Monad Transformers
- mtl library documentation
Related Libraries
- mtl: The standard MTL library
- transformers: Lower-level transformer types without MTL classes
- polysemy: Algebraic effects as alternative
- fused-effects: Another effect system
- rio: ReaderT IO pattern library
Conclusion
Monad transformers solve a fundamental problem in functional programming: how to compose effects. By building transformers from scratch, youâve learned:
- Why monads donât compose - The need for specialized composition
- The structure of transformers - How each wraps effects around a base monad
- The lift operation - Injecting base actions into the stack
- Stack ordering - Why the order of transformers matters
- MTL style - Abstracting over stacks with type classes
You now have the skills to build complex effect-ful programs with clear, composable structure.
Next Steps:
- Project 10: Property-Based Testing - Use transformers in a QuickCheck clone
- Project 11: Lenses and Optics - Compose data access patterns