Monad transformers are a way to combine multiple monads to create a composite monad that has the features of all the component monads.
The Problem: Combining Monads
Different monads provide different computational effects:
Maybe- Computations that might failEither e- Computations that might fail with an error of typeeReader r- Computations with read-only access to an environment of typerState s- Computations with mutable state of typesIO- Computations with side effects
But what if we need multiple effects? For example:
- A computation that needs access to configuration AND might fail
- A computation that maintains state AND performs IO operations
We can’t easily compose monads directly. If we have functions:
f :: a -> Maybe b
g :: b -> State s cThere’s no general way to compose them to get a function a -> SomeCombinedMonad c.
Monad Transformers: The Solution
Monad transformers are special types that add capabilities of one monad to another monad.
Key transformer types include:
MaybeT m a- AddsMaybe’s failure handling to monadmExceptT e m a- AddsEither e’s error handling to monadmReaderT r m a- AddsReader r’s environment access to monadmStateT s m a- AddsState s’s state manipulation to monadmWriterT w m a- AddsWriter w’s logging to monadm
The MonadTrans Typeclass
The MonadTrans typeclass defines how to lift operations from the base monad into the transformer:
class MonadTrans t where
lift :: (Monad m) => m a -> t m aThis allows operations from the inner monad to be used in the context of the transformer.
Common Monad Transformers
MaybeT
Adds optional values to any monad:
newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }
instance (Monad m) => Monad (MaybeT m) where
return = MaybeT . return . Just
x >>= f = MaybeT $ do
v <- runMaybeT x
case v of
Nothing -> return Nothing
Just y -> runMaybeT (f y)
instance MonadTrans MaybeT where
lift = MaybeT . fmap JustExample
import Control.Monad.Trans.Maybe
import Control.Monad.Trans.Class
findUser :: UserId -> MaybeT IO User
findUser uid = do
mUser <- lift $ queryDatabase uid
case mUser of
Nothing -> MaybeT $ return Nothing
Just user -> return user
getUserSettings :: User -> MaybeT IO Settings
getUserSettings user = do
mSettings <- lift $ fetchSettings (userId user)
MaybeT $ return mSettings
userProgram :: UserId -> IO (Maybe Settings)
userProgram uid = runMaybeT $ do
user <- findUser uid
getUserSettings userExceptT
Adds error handling to any monad:
newtype ExceptT e m a = ExceptT { runExceptT :: m (Either e a) }Example
import Control.Monad.Trans.Except
import Control.Monad.Trans.Class
data AppError = NotFound | PermissionDenied | ServerError String
deriving Show
type AppM a = ExceptT AppError IO a
findDocument :: DocId -> AppM Document
findDocument docId = do
mDoc <- lift $ queryDatabase docId
case mDoc of
Nothing -> throwE NotFound
Just doc -> return doc
checkPermission :: UserId -> Document -> AppM ()
checkPermission userId doc = do
hasPermission <- lift $ checkUserPermission userId doc
unless hasPermission $ throwE PermissionDenied
processDocument :: UserId -> DocId -> IO (Either AppError ProcessedDoc)
processDocument userId docId = runExceptT $ do
doc <- findDocument docId
checkPermission userId doc
lift $ processDoc docReaderT
Adds read-only environment to any monad:
newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }Example
import Control.Monad.Reader
import Control.Monad.Trans.Class
data Config = Config {
apiUrl :: String,
timeout :: Int,
maxRetries :: Int
}
type AppM a = ReaderT Config IO a
fetchData :: Endpoint -> AppM Data
fetchData endpoint = do
config <- ask
let url = apiUrl config ++ endpoint
to = timeout config
lift $ httpGet url to
retryOperation :: AppM a -> AppM a
retryOperation operation = do
config <- ask
lift $ withRetry (maxRetries config) (runReaderT operation config)
appMain :: Config -> IO Result
appMain config = runReaderT program config
where
program = do
userData <- fetchData "/users"
productData <- fetchData "/products"
return (processResults userData productData)StateT
Adds mutable state to any monad:
newtype StateT s m a = StateT { runStateT :: s -> m (a, s) }Example
import Control.Monad.State
import Control.Monad.Trans.Class
type GameState = (Player, World)
type GameM a = StateT GameState IO a
movePlayer :: Direction -> GameM ()
movePlayer dir = do
(player, world) <- get
let newPlayer = updatePosition player dir
if isValidPosition world newPlayer
then put (newPlayer, world)
else return ()
interactWithObject :: GameM ()
interactWithObject = do
(player, world) <- get
case objectAt world (playerPosition player) of
Nothing -> lift $ putStrLn "Nothing here."
Just obj -> do
lift $ putStrLn $ "Interacting with " ++ show obj
let (newWorld, message) = interact world obj
put (player, newWorld)
lift $ putStrLn message
gameLoop :: GameM ()
gameLoop = do
(player, _) <- get
if playerHealth player <= 0
then lift $ putStrLn "Game over!"
else do
cmd <- lift getCommand
executeCommand cmd
gameLoop
runGame :: GameState -> IO ()
runGame initialState = evalStateT gameLoop initialStateTransformer Stacks
Monad transformers can be stacked to combine multiple effects:
type AppM a = ExceptT AppError (ReaderT Config (StateT AppState IO)) aThis gives us a monad with:
- Error handling (ExceptT)
- Configuration access (ReaderT)
- Mutable application state (StateT)
- IO capabilities (IO)
Running a Transformer Stack
To run a monad transformer stack, you apply the “run” functions from outside in:
runApp :: Config -> AppState -> AppM a -> IO (Either AppError a, AppState)
runApp config state action =
runStateT (runReaderT (runExceptT action) config) stateExample: Complex Stack
{-# LANGUAGE FlexibleContexts #-}
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad.Except
import Control.Monad.Writer
data AppConfig = AppConfig { ... }
data AppState = AppState { ... }
data AppError = AppError { ... }
type Log = [String]
type AppM a = ExceptT AppError (ReaderT AppConfig (StateT AppState (WriterT Log IO))) a
-- Access config
getConfig :: MonadReader AppConfig m => m AppConfig
getConfig = ask
-- Access/modify state
getState :: MonadState AppState m => m AppState
getState = get
updateState :: MonadState AppState m => (AppState -> AppState) -> m ()
updateState = modify
-- Error handling
throwAppError :: MonadError AppError m => AppError -> m a
throwAppError = throwError
-- Logging
logInfo :: MonadWriter Log m => String -> m ()
logInfo msg = tell [msg]
-- IO operations
liftIOOperation :: MonadIO m => IO a -> m a
liftIOOperation = liftIO
-- Running the application
runApp :: AppConfig -> AppState -> AppM a -> IO (((Either AppError a, AppState), Log))
runApp config state app =
runWriterT (runStateT (runReaderT (runExceptT app) config) state)Lifting Through Transformer Stacks
When working with transformer stacks, you often need to lift operations:
-- Lift from innermost monad to transformer stack
liftIO :: MonadIO m => IO a -> m a
-- Lifting through a stack requires multiple lifts
liftMaybeIO :: MaybeT (StateT s IO) a -> ExceptT e (ReaderT r (StateT s IO)) a
liftMaybeIO = lift . lift . lift . except . maybe (Left defaultError) Right . runMaybeTType Classes for Lifting
The mtl library provides typeclasses for different monad capabilities:
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
class Monad m => MonadWriter w m | m -> w where
tell :: w -> m ()
listen :: m a -> m (a, w)
pass :: m (a, w -> w) -> m aThese typeclasses make it easier to write code that works with any transformer stack that has the required capabilities.
Common Patterns with Monad Transformers
The ReaderT IO Pattern
The ReaderT env IO monad is a common pattern for applications:
newtype App a = App { unApp :: ReaderT Env IO a }
deriving (Functor, Applicative, Monad, MonadReader Env, MonadIO)
-- All functions can access the environment
getConfig :: App Config
getConfig = asks envConfig
-- Lift IO operations
logMessage :: String -> App ()
logMessage msg = do
logger <- asks envLogger
liftIO $ logger msg
-- Run the application
runApp :: Env -> App a -> IO a
runApp env app = runReaderT (unApp app) envError Handling with ExceptT
Adding error handling with ExceptT:
type App a = ExceptT AppError (ReaderT Env IO) a
-- Now we can throw and catch errors
saveDocument :: Document -> App ()
saveDocument doc = do
db <- asks envDatabase
result <- liftIO $ tryIOError $ writeToDatabase db doc
case result of
Left e -> throwError (DatabaseError e)
Right _ -> return ()
-- Run with error handling
runApp :: Env -> App a -> IO (Either AppError a)
runApp env app = runReaderT (runExceptT app) envState with StateT
Adding state management:
type App a = StateT AppState (ReaderT Env (ExceptT AppError IO)) a
-- Update state based on external operations
processTransaction :: Transaction -> App Balance
processTransaction tx = do
AppState {balance} <- get
let newBalance = updateBalance balance tx
if newBalance < 0
then throwError InsufficientFunds
else do
modify $ \s -> s {balance = newBalance}
return newBalance
-- Run with state
runApp :: Env -> AppState -> App a -> IO (Either AppError (a, AppState))
runApp env state app = runExceptT $ runReaderT (runStateT app state) envMonad Transformer Best Practices
1. Keep the Stack Simple
Don’t add transformers you don’t need. A common stack is:
type App a = ExceptT AppError (ReaderT Env IO) aThis gives you:
- Error handling (ExceptT)
- Environment access (ReaderT)
- IO capabilities (IO)
2. Use Type Classes
Instead of directly referencing your transformer stack, use typeclasses:
-- Instead of this:
fetchUser :: UserId -> ExceptT Error (ReaderT Env IO) User
-- Prefer this:
fetchUser :: (MonadReader Env m, MonadError Error m, MonadIO m) => UserId -> m UserThis makes your code more reusable and easier to test.
3. Define Helper Functions
Create helpers for common operations:
throwDbError :: MonadError AppError m => DbError -> m a
throwDbError = throwError . DatabaseError
withTransaction :: (MonadReader Env m, MonadError AppError m, MonadIO m) => (Connection -> IO a) -> m a
withTransaction action = do
conn <- asks envDbConnection
result <- liftIO $ try $ withDbTransaction conn action
either throwDbError return result4. Use Newtypes for Your App Monad
newtype App a = App { runApp :: ExceptT AppError (ReaderT Env IO) a }
deriving (Functor, Applicative, Monad, MonadReader Env, MonadError AppError, MonadIO)This gives you better type safety and lets you define custom instances.
5. Consider Performance
Monad transformers can introduce overhead. For performance-critical applications, consider alternatives like the RIO or ReaderT IO patterns.
Key Points to Remember
- Monad transformers let you combine multiple monadic effects
- Each transformer adds a specific capability (error handling, state, etc.)
- Use
liftto promote operations from inner monads to the transformer stack - The mtl library provides typeclasses for common monadic capabilities
- The order of transformers matters - effects are applied from inner to outer
- Common patterns include
ReaderT Env IOandExceptT Error (ReaderT Env IO) - Use typeclasses and helper functions to make your code more modular
Error handling in Haskell differs significantly from exception-based approaches in imperative languages. Haskell provides several approaches that align with its functional nature and type system. For background on types and monads, see Algebraic Data Types, Common Monads, and Monads Basics.
Types of Errors in Haskell
- Compile-time errors: Type errors, syntax errors, etc.
- Runtime errors: Exceptions that occur during program execution
- Expected failures: Situations where operations might legitimately fail
This page focuses on handling the last two categories.
Approaches to Error Handling
1. Maybe Type
The Maybe type represents computations that might fail. This is a common pattern in Haskell and is discussed in more detail in Common Monads and Algebraic Data Types.
Working with Multiple Maybe Values
Using do notation with Maybe leverages the monadic structure described in Monads Basics.
2. Either Type
The Either type provides more detailed error information. Like Maybe, it is an algebraic data type (see Algebraic Data Types) and a common monad (Common Monads).
Working with Multiple Either Values
Chaining Either computations with do notation is another example of monadic error handling (see Monads Basics).
3. ExceptT Monad Transformer
ExceptT combines the Either type with another monad (often IO). For more on combining effects, see Monad Transformers. For IO, see Introduction to IO.
4. Runtime Exceptions
Haskell has a system for runtime exceptions, but idiomatic Haskell code prefers explicit error types like Maybe and Either (see above and Common Monads).
5. Custom Exceptions
You can define custom exception types using algebraic data types (see Algebraic Data Types).