-
Why do we like monad transformers?
- they let us deal with more than one level of structure without having to deal with more than one level of structure by hand every time we encounter it.
-
When will we have to write our own instances?
- not too frequently! Everything in the chapter that we have to write is already
available in
transformers
underControl.Monad.Trans.<thing>
- not too frequently! Everything in the chapter that we have to write is already
available in
-
What will we use in practice?
ReaderT
,StateT
,MaybeT
,EitherT
, but also maybe, since we're a long ways off using haskell at work. We won't useWriterT
because the book said not to (it does bad coupling), and we also won't use things likeListT
because there are streaming IO libraries that do a better job (pipes
,conduit
)
-
How is
StateT
likeParser
?StateT
hasrunState :: a -> m (a, s)
.Parser a
s haveparse :: String -> Maybe (a, String)
.Parser a
s areStateT String Maybe
s. Great.
-
What's
MonadTrans
all about?MonadTrans
is a typeclass that provides uslift :: (Monad m) => m a -> t m a
. We start with a monad and end up with a monad transformer type. Stylish.
-
How are you going to stick a pipe in your own bicycle wheels with
MonadTrans
?- by doing this:
i <- WidgetT $ lift $ lift $ lift $ lift $ lift $ lift $ lift
Don't do that. Instead, newtype your monad stack and provide a
MonadTrans
class for the newtype, so you can just have the onelift
-
What's
MonadIO
all about?-
A common pattern is to have a bunch of
Monad
stuff wrapped in anIO
. It would be a bit of a drag to have to newtype everyIO <MonadStack>
and writeMonadTrans
instances every time (apparently), soliftIO
does that for you. Here'sMonadIO
:class (Monad m) => MonadIO m where liftIO :: IO a -> m a
liftIO
keeps lifting until it runs out ofMonad
s
-
-
Will you die from not fully grokking monad transformers the first time?
-
probably not! Haskell book says "Most of the time you can get by with liftIO and plain IO actions". Cats says
OptionT[F[_], A] is a light wrapper on an F[Option[A]]. Speaking technically, it is a monad transformer for Option, but you don’t need to know what that means for it to be useful.
-
Last active
January 30, 2018 13:33
-
-
Save jisantuc/32bc80a11f64e6496227317575f37b82 to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module InChapter where | |
{-# LANGUAGE OverloadedStrings #-} | |
import Control.Monad.IO.Class | |
import Control.Monad.Trans.Except | |
import Control.Monad.Trans.Maybe | |
import Control.Monad.Trans.Reader | |
-- EitherT | |
---------------------- | |
newtype EitherT e m a = | |
EitherT { runEitherT :: m (Either e a) } | |
instance Functor m | |
=> Functor (EitherT e m) where | |
fmap f ema = EitherT $ (fmap . fmap) f (runEitherT ema) | |
instance Applicative m | |
=> Applicative (EitherT e m) where | |
pure = EitherT . (pure . pure) | |
-- lift the application over the EitherT structure into the inner monad around | |
-- an either | |
(<*>) (EitherT (fab)) (EitherT mma) = | |
EitherT $ (<*>) <$> fab <*> mma | |
instance Monad m | |
=> Monad (EitherT e m) where | |
return = pure | |
(EitherT mea) >>= f = | |
EitherT $ do | |
ea <- mea | |
case ea of | |
Right y -> | |
runEitherT (f y) | |
-- without `return (Left x)` (i.e., using just `x`, which is obviously `Left x`), | |
-- the compiler gets the type inference wrong, I _think_ because x is a `Left x` | |
-- of type `Either e a`, while creating a new `Either` on the right side of the `->` | |
-- is a `Left x` of type `Either e b` | |
Left x -> | |
return (Left x) | |
-- for when you decide your error type is your success type? no idea | |
swapEither :: Either e a -> Either a e | |
swapEither (Right x) = Left x | |
swapEither (Left x) = pure x | |
-- for when you decide your error type is your success type | |
-- _in the presence of additional structure_ my god what why would this ever happen | |
swapEitherT :: (Functor m) | |
=> EitherT e m a | |
-> EitherT a m e | |
swapEitherT (EitherT ma) = EitherT $ swapEither <$> ma | |
-- catamorphism for when you _really_ want an m c | |
eitherT :: Monad m | |
=> (a -> m c) | |
-> (b -> m c) | |
-> EitherT a m b | |
-> m c | |
eitherT f g (EitherT amb) = | |
do | |
aOrB <- amb | |
case aOrB of | |
(Left x) -> f x | |
(Right y) -> g y | |
-- StateT | |
---------------------- | |
-- solutions shamelessly stolen from reddit because I only sort of understand what's going on | |
newtype StateT s m a = | |
StateT { runStateT :: s -> m (a, s) } | |
instance Functor m | |
=> Functor (StateT s m) where | |
fmap f (StateT g) = StateT $ (fmap . fmap) applyToA g | |
where applyToA (a, s) = (f a, s) | |
instance (Monad m) => Applicative (StateT s m) where | |
pure a = StateT $ \s -> pure (a, s) | |
(<*>) (StateT f) (StateT g) = | |
StateT | |
$ \s -> f s | |
>>= \(f', s') -> (\(a, s) -> (f' a, s) ) | |
<$> g s' | |
instance Monad m => Monad (StateT s m )where | |
return = pure | |
(>>=) (StateT f) g = | |
StateT | |
$ \s -> f s | |
>>= \(a, s') -> (runStateT . g) a s' | |
-- wrapping a weird thing back up | |
embedded :: MaybeT (ExceptT String (ReaderT () IO)) Int | |
embedded = return 1 | |
unwrapped :: Either () (Maybe Int) | |
unwrapped = (const . Right . Just $ 1) () | |
rewrapped :: MaybeT (ExceptT String (ReaderT () IO )) Int | |
rewrapped = undefined -- smth (const (Right (Just 1))) | |
-- MonadIO instances | |
-- I think this should work, since you end up with the inner monad | |
-- `liftIO` handling transformation of whatever `m` is and a `MaybeT` | |
-- on the outside, which would be necessary for sequencing `MaybeT`s, | |
-- but duplicate instances and all that | |
--instance (MonadIO m) | |
-- => MonadIO (MaybeT m) where | |
-- liftIO = MaybeT . liftIO | |
-- Chapter Exercises | |
-- no. |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- scotty.hs | |
{-# LANGUAGE OverloadedStrings #-} | |
module Scotty where | |
import Web.Scotty | |
import Control.Monad.Trans.Class | |
import Control.Monad.IO.Class | |
import Data.Monoid (mconcat) | |
-- the stuff inside scotty 3000 is an ActionT, | |
-- which defines lift in its MonadTrans instance as | |
-- instance MonadTrans (ActionT e) where | |
-- lift = ActionT . lift . lift . lift | |
-- all those lifts are from the newtype for ActionT, | |
-- which is | |
-- newtype ActionT e m a = | |
-- ActionT { | |
-- runAM | |
-- :: ExceptT | |
-- (ActionError e) | |
-- (ReaderT ActionEnv (StateT ScottyResponse m)) | |
-- a | |
-- } deriving (Functor, Applicative) | |
-- so the `lift`s cover magical monad transformation for all | |
-- of the parameterized types of `ActionT` | |
main = scotty 3000 $ do | |
get "/:word" $ do | |
beam <- param "word" | |
-- lift $ putStrLn "hello" | |
liftIO (putStrLn "hello") | |
-- putStrLn "hello" | |
html $ | |
mconcat ["<h1>Scotty, ", | |
beam, | |
" me up!</h1>"] |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment