You can look at monads as ways to represent effects.
Monad | Effect |
---|---|
Maybe | Computation can fail (store 0 or 1 values). |
Either | Computation can fail with an annotated error. |
[] | Computation stores 0 or more values. |
Writer | Computation has a monoidal logging accumulator. |
Reader | Computation has access to some immutable environment. |
State | Computation is stateful. |
IO | Computation can perform I/O actions. |
We want to write functions that have access to multiple effects. ⇒ We want to compose effects.
Let's look at Reader (usually effects can be represented as functions).
foo :: String -> Env -> Int
foo :: String -> Reader Env Int
Simple for beginners
Effect is handled automatically
foo :: UnknownType
foo i = do
baseCounter <- ask
let newCounter = baseCounter + i
put [baseCounter, newCounter]
return newCounter
newtype RWS r w s a = RWS
{ runRWS :: r -> s -> (a, s, w) }
foo :: RWS Int () [Int] Int
foo i = do
baseCounter <- ask
let newCounter = baseCounter + i
put [baseCounter, newCounter]
return newCounter
foo :: State (Int, [Int]) Int
foo i = do
x <- gets fst
let xi = x + i
put (x, [x, xi])
return xi
foo :: Int -> ReaderT Int (State [Int]) Int -- or StateT [Int] (Reader Int) Int
foo i = do
baseCounter <- ask
let newCounter = baseCounter + i
put [baseCounter, newCounter]
return newCounter
newtype (g |.| f) a = Compose { getCompose :: g (f a) }
Functors and Applicatives compose. Monads, in general — don't.
If f is a Functor and g is a Functor, then composition of g and f is also a Functor (i.e. g |.| f is a Functor). Same for Applicative, Alternative, Foldable, Traversable.
instance (Functor f, Functor g) => Functor (g |.| f)
instance (Foldable f, Foldable g) => Foldable (g |.| f)
instance (Traversable f, Traversable g) => Traversable (g |.| f)
instance (Applicative f, Applicative g) => Applicative (g |.| f)
instance (Alternative f, Alternative g) => Alternative (g |.| f)
instance (Monad f, Monad g) => Monad (g |.| f) -- impossible in general
Composition of two Monads is not always a Monad.
tryConnect :: HostName -> IO (Maybe Connection)
foo :: IO (Maybe smth)
foo = do
mc1 <- tryConnect "host1"
case mc1 of
Nothing -> return Nothing
Just c1 -> do
mc2 <- tryConnect "host2"
case mc2 of
Nothing -> return Nothing
Just c2 -> do
...
newtype MaybeIO a = MaybeIO { runMaybeIO :: IO (Maybe a) }
instance Monad MaybeIO where
return x = MaybeIO (return (Just x))
MaybeIO action >>= f = MaybeIO $ do
result <- action
case result of
Nothing -> return Nothing
Just x -> runMaybeIO (f x)
result <- runMaybeIO $ do
c1 <- MaybeIO $ tryConnect "host1"
c2 <- MaybeIO $ tryConnect "host2"
...
result <- runMaybeIO $ do
c1 <- MaybeIO $ tryConnect "host1"
print "Hello" -- typechecking fails, but what if we REALLY want to do this?
c2 <- MaybeIO $ tryConnect "host2"
Nice
But what about this?
liftIOToMaybeIO :: IO a -> MaybeIO a
liftIOToMaybeIO action = MaybeIO $ do
result <- action
return (Just result)
result <- runMaybeIO $ do
c1 <- MaybeIO $ tryConnect "host1"
liftIOToMaybeIO $ print "Hello"
c2 <- MaybeIO $ tryConnect "host2"
...
Charming
liftIOToMaybeIO :: IO a -> MaybeIO a
liftIOToMaybeIO action = MaybeIO $ Just <$> action
type MaybeIO = MaybeT IO
instance Monad m => Monad (MaybeT m) where
return :: a -> MaybeT m a
return x = MaybeT (return (Just x))
(>>=) :: MaybeT m a -> (a -> MaybeT m b) -> MaybeT m b
MaybeT action >>= f = MaybeT $ do
result <- action
case result of
Nothing -> return Nothing
Just x -> runMaybeT (f x)
newtype MaybeT m a = MaybeT
{ runMaybeT :: m (Maybe a) }
liftToMaybeT :: Functor m => m a -> MaybeT m a
liftToMaybeT = MaybeT . fmap Just
class MonadTrans t where -- t :: (Type -> Type) -> Type -> Type
-- all monad transformers have exactly this type
-- all monad transformers instantiate MonadTrans
lift :: Monad m => m a -> t m a
liftToMaybeT :: Monad m => m a -> MaybeT m a
liftToExceptT :: Monad m => m a -> ExceptT e m a
instance MonadTrans MaybeT where
lift :: Monad m => m a -> MaybeT m a
lift = liftToMaybeT
1. lift . return ≡ return
2. lift (m >>= f) ≡ lift m >>= (lift . f)
3. lift . join = join . lift . fmap lift -- redundant, but still valid
emailIsValid :: String -> Bool
emailIsValid email = '@' `elem` email
askEmail :: IO (Maybe String)
askEmail = do
putStrLn "Input your email, please:"
email <- getLine
return $ if emailIsValid email
then Just email
else Nothing
main :: IO ()
main = do
email <- askEmail
case email of
Nothing -> putStrLn "Wrong email."
Just email' -> putStrLn $ "OK, your email is " ++ email'
emailIsValid :: String -> Bool
emailIsValid email = '@' `elem` email
askEmail :: MaybeT IO String
askEmail = do
lift $ putStrLn "Input your email, please:"
email <- lift getLine
guard $ emailIsValid email
return email
main :: IO ()
main = do
email <- runMaybeT askEmail
case email of
Nothing -> putStrLn "Wrong email."
Just email' -> putStrLn $ "OK, your email is " ++ email'
main :: IO ()
main = do
Just email <- runMaybeT $ untilSuccess askEmail
putStrLn $ "OK, your email is " ++ email
untilSuccess :: Alternative f => f a -> f a
untilSuccess = foldr (<|>) empty . repeat
-- Defined in Control.Monad.Trans.Maybe
instance (Functor m, Monad m) => Alternative (MaybeT m) where
empty = MaybeT (return Nothing)
x <|> y = MaybeT $ runMaybeT x >>= maybe (runMaybeT y) (return . Just)
newtype LoggerName = LoggerName { getLoggerName :: Text }
logMessage :: LoggerName -> Text -> IO ()
readFileWithLog :: LoggerName -> FilePath -> IO Text
readFileWithLog loggerName path = do
logMessage loggerName $ "Reading file: " <> T.pack (show path)
readFile path
main :: IO ()
main = prettifyFileContent (LoggerName "Application") "foo.txt"
writeFileWithLog :: LoggerName -> FilePath -> Text -> IO ()
writeFileWithLog loggerName path content = do
logMessage loggerName $ "Writing to file: " <> T.pack (show path)
writeFile path content
prettifyFileContent :: LoggerName -> FilePath -> IO ()
prettifyFileContent loggerName path = do
content <- readFileWithLog loggerName path
writeFileWithLog loggerName path (format content)
type LoggerIO = ReaderT LoggerName IO
logMessage :: Text -> LoggerIO ()
readFileWithLog :: FilePath -> LoggerIO Text
readFileWithLog path = do
logMessage $ "Reading file: " <> T.pack (show path)
lift $ readFile path
main :: IO ()
main = runReaderT (prettifyFileContent "foo.txt") (LoggerName "Application")
writeFileWithLog :: FilePath -> Text -> LoggerIO ()
writeFileWithLog path content = do
logMessage $ "Writing to file: " <> T.pack (show path)
lift $ writeFile path content
prettifyFileContent :: FilePath -> LoggerIO ()
prettifyFileContent path = do
content <- readFileWithLog path
writeFileWithLog path (format content)
newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
newtype ReaderT r m a = ReaderT
{ runReaderT :: r -> m a }
type Reader r
= ReaderT r Identity
type LoggerIO
= ReaderT LoggerName IO
instance Monad m => Monad (ReaderT r m) where
return = lift . return
m >>= f = ReaderT $ \r -> do
a <- runReaderT m r
runReaderT (f a) r
instance MonadTrans (ReaderT r) where
lift :: m a -> ReaderT r m a
lift = ReaderT . const
-- lift ma = ReaderT $ \_ -> ma
Precursor | Transformer | Original type | Combined type |
---|---|---|---|
Maybe | MaybeT | Maybe a | m (Maybe a) |
Either | ExceptT | Either a b | m (Either a b) |
Writer | WriterT | (a, w) | m (a, w) |
Reader | ReaderT | r -> a | r -> m a |
State | StateT | s -> (a, s) | s -> m (a, s) |
Cont | ContT | (a -> r) -> r | (a -> m r) -> m r |
class Monad m => MonadIO m where
liftIO :: IO a -> m a
instance MonadIO IO where
liftIO = id
instance MonadIO m => MonadIO (StateT s m) where
liftIO = lift . liftIO
instance MonadIO m => MonadIO (ReaderT r m) where
liftIO = lift . liftIO
etc.
Try writing a Monad instance for IOT and deduce the issue yourself!
foo :: Int -> StateT [Int] (Reader Int) Int
foo i = do
baseCounter <- lift ask
let newCounter = baseCounter + i
put [baseCounter, newCounter]
return newCounter
class Monad m => MonadReader r m | m -> r where
ask :: m r
local :: (r -> r) -> m a -> m a
reader :: (r -> a) -> m a
instance MonadReader r m => MonadReader r (StateT s m) where
ask = lift ask
local = mapStateT . local
reader = lift . reader
-- good old simple implementation of all the Reader functions
instance Monad m => MonadReader r (ReaderT r m) where ...
foo :: Int -> StateT [Int] (Reader Int) Int
foo i = do
baseCounter <- ask
let newCounter = baseCounter + i
put [baseCounter, newCounter]
return newCounter
newtype Parser a = Parser { runParser :: String -> Maybe (a, String) }
newtype StateT s m a = StateT { runStateT :: s -> m (a, s) }
type Parser = StateT String Maybe
Recall our Parser type:
It's just a StateT specialization for more concrete types!
class Monad m => MonadThrow m where
throwM :: Exception e => e -> m a
class MonadThrow m => MonadCatch m where
catch :: Exception e => m a -> (e -> m a) -> m a
instance MonadThrow Maybe where
throwM _ = Nothing
instance MonadThrow IO where
throwM = Control.Exception.throwIO
instance MonadThrow m => MonadThrow (StateT s m) where
throwM = lift . throwM
instance MonadCatch IO where
catch = Control.Exception.catch
class Monad m => MonadError e m | m -> e where
throwError :: e -> m a
catchError :: m a -> (e -> m a) -> m a
foo :: MonadError FooError m => ...
bar :: MonadError BarError m => ...
baz :: MonadError BazError m => ...
data BazError = BazFoo FooError | BazBar BarError
baz = do
withExcept BazFoo foo
withExcept BazBar ba
newtype ExceptT e m a = ExceptT { runExceptT :: m (Either e a) }
runExceptT :: ExceptT e m a -> m (Either e a)
instance Monad m => MonadError e (ExceptT e m) where ...
withExceptT :: Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a
This helps to avoid writing lift manually...
Has only the MonadTrans typeclass and the classic monad transformer types (ReaderT, StateT, etc.)
Reexports transformers. For each monad SomeT adds a MultiParamTypeClass MonadSome with FunctionalDependencies.
Cost: the n * m instances problem.
If you have n monads and m typeclasses, you need to write n * m instances. But usually these instances are trivial one-liners.
-- A complex type for which we need to write all the instances manually :(
newtype M a = M (Environment -> MyState -> IO (a, MyState))
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
-- Leave all the dirty work to the compiler
newtype M a = M (ReaderT Environment (StateT MyState IO) a)
deriving (Functor, Applicative, Monad, MonadIO,
MonadState MyState, MonadReader Environment)
foo :: Text -> M Text
foo :: ( MonadState MyState m
, MonadReader Environment m
, MonadIO m
) => Text -> m Text
foo ::
Context = m
Effects m =
Needs Env
, Updates Stack
, Throws EmptyStackError
, Reads "config/application.toml"
Type = Int -> Int -> m [Int]
foo :: ( MonadReader Env m
, MonadState Stack m
, MonadError EmptyStackError m
, MonadIO m
)
=> Int -> Int -> m [Int]
data Env = Env
{ envServerAddress :: Text
, envConn :: IORef (Maybe Conn)
}
establishConn :: ReaderT Env IO ()
establishConn = do
Env sAddr cRef <- ask
prev <- liftIO $ readIORef cRef
whenNothing prev $
throwM ConnectionExists
liftIO $
connect sAddr >>=
writeIORef cRef . Just
data AppError = ConnectionExists
deriving Show
instance Exception AppError
data Name = Name String
data User = User { name :: Name
, age :: Int }
class Monad m => MonadDatabase m where
getUser :: Name -> m User
deleteUser :: User -> m ()
test :: MonadDatabase m => m ()
test = do
user <- getUser (Name "Pedro")
when (age user < 18) (deleteUser user)
newtype AppM a = AppM (ReaderT Ctx IO a)
newtype TestM a = TestM (State [User] a)
main :: IO ()
main = runAppM test
Unless you write a library, just use the concrete monad!
When you want to test your application code in pure way.
foo :: ExceptT Err IO ()
bar :: StateT St IO ()
foobar :: ExceptT Err (StateT St IO) ()
-- Good way
foo :: ReaderT Ctx
(ExceptT Err (State St)) ()
-- Little bit less efficient
bar :: ExceptT Err
(StateT MyState (Reader Ctx)) ()
-- Fragile code!
foobar :: ExceptT Err (Except Err) ()
ExceptT doesn't add anything to error handling in IO.
StateT is hard to safely handle with IO exceptions, the use of IORef should be preferred.
Be careful about the order of transformer composition.
With StateT over ExceptT wrong state might be restored after catch.
There are a lot of custom defined Monad* classes in the mtl style
Monad transformers solve so-called Extensible effects problem. There exist different approaches for this problem, but monad transformers is the most popular and fastest approach.
eval : Expr -> Eff Integer [STDIO, EXCEPTION String, RND, STATE Env]
data Expr = Val Integer
| Var String
| Add Expr Expr
| Random Integer
More expressive, huh?
Idris rulit' i razrulivaet?
data RandomGen = RandomGen
data WriteLn = WriteLn { unWriteLn :: String }
type instance EffectRes RandomGen = Int
type instance EffectRes WriteLn = ()
myExecution :: Free (MyF '[ RandomGen , WriteLn ]) Int
myExecution = do
rand1 <- effect RandomGen
rand2 <- effect RandomGen
effect $ WriteLn $ "Generated two random numbers: "
<> show rand1 <> " " <> show rand2
pure $ rand1 ^ 2 + rand2
runExecution :: IO Int
runExecution = iterM (runMyF handlers) myExecution
where
handlers = Handler (const randomIO) :& Handler (putStrLn . unWriteLn) :& RNil
Haskell allows you to write essentially exactly the same code.
Full code uses free monads, DataKinds and other advanced machinery. To be continued on next lectures.
-- | The CoroutineT monad is just ContT stacked with
-- a StateT containing the suspended coroutines.
newtype CoroutineT r m a = CoroutineT
{ runCoroutineT' :: ContT r (StateT [CoroutineT r m ()] m) a
} deriving (Functor, Applicative, Monad, MonadCont, MonadIO)
printOne n = do
liftIO (print n)
yield
example = runCoroutineT $ do
fork $ replicateM_ 3 (printOne 3)
fork $ replicateM_ 4 (printOne 4)
replicateM_ 2 (printOne 2)
3
4
3
2
4
3
2
4
4
...some implementation details ~50 lines...