Type constructor with unit (return
) and bind (>>=
),
class Monad (m :: * -> *) where
return :: a -> m a
(>>=) :: m a -> (a -> m b) -> m b
satisfying the following laws:
return x >>= f == f x
m >>= return == m
(m >>= f) >>= g == m >>= (\ x -> f x >>= g)
State Int
increment :: State Int ()
increment = do
x <- get
put $ x+1
IO
main :: IO ()
main = do
putStrLn $ "What is your name?"
x <- getLine
putStrLn $ "Hello, " ++ x ++ "!"
The underlying functors compose!
State s (Maybe (IO a))
Monads with a "hole" for another monad
Values in the inner monad can be lifted to the outer
class MonadTrans (f :: (* -> *) -> * -> *) where
lift :: Monad m => m a -> t m a
lift
must respect return
and >>=
lift . return = return
lift (m >>= f) = lift m >>= (lift . f)
Examples
newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)}
instance MonadTrans MaybeT where
lift = MaybeT . liftM Just
type Maybe a = MaybeT Identity a
newtype StateT s m a = StateT {runStateT :: s -> m (a, s)}
instance MonadTrans (StateT s) where
lift m = StateT $ \ s -> do
a <- m
return (a, s)
type State s a = StateT s Identity a
We have
StateT s Maybe a ≠ MaybeT (State s) a
because
s -> Maybe (s , a) ≠ s -> (s , Maybe a)
Monolithic effects
data TheMonadOfMyApp a =
TheMonadOfMyApp (MyState -> (IO (MyLog , MyState , a)))
instance Monad TheMonadOfMyApp where
...
justSayHello :: TheMonadOfMyApp ()
justSayHello = TheMonadOfMyApp $ \ db -> do
putStrLn $ "Hello!"
return ("Just said hello!" , db , ())
main :: IO ()
main = runTheMonadOfMyApp initialState $ do
justSayHello
...
We would prefer
justSayHello :: StdOutput ()
justSayHello = putStrLn "Hello!"
or
justSayHello :: StdOutput m => m ()
justSayHello = putStrLn "Hello!"
It should also be easy to add a new effect to our "vocabulary"
There should be no need to
Use type classes to capture monadic interfaces
standard monad transformers
+
type classes with their abstract interfaces
See Jones 1995
increment :: State Int ()
increment = do
x <- get
put $ x+1
becomes
increment :: MonadState Int m => m ()
increment = do
x <- get
put $ x+1
main :: IO ()
main = do
putStrLn $ "What is your name?"
x <- getLine
putStrLn $ "Hello, " ++ x ++ "!"
becomes
main :: MonadIO m => m ()
main = do
putStrLn $ "What is your name?"
x <- getLine
putStrLn $ "Hello, " ++ x ++ "!"
State
s in the stackDue to functional dependency!
class Monad m => MonadState s m | m -> s where
get :: m s
put :: s -> m ()
If you omit | m -> s
, you need OverlappingInstances
Same for MonadReader
and MonadWriter
.
program
?program :: (MonadError () m , MonadState s m) => m ()
To add the (n+1)-th monad transformer,
we must give n instances.
lift
is extremely ad hoc!
Represent effectful programs as modular syntax
Handlers interpret syntax as monads
A datatype parameterised by a f :: * -> *
operator
data Free f a =
Return a
| Free (f (Free f a))
When f
is a Functor
, Free f
is a Monad
!
instance Functor f => Monad (Free f) where
return = Return
(Return a) >>= f = f a
(Free xs) >>= f = Free (fmap (>>= f) xs)
We use Free a
as a generic representation for monadic computations
Free f
?
Example: Take f = Arithmetics
data Arithmetics a =
Val Int
| Plus a a
deriving Functor
Free Arithmetics x
represents expressions made from
+
x
Free f
?
Take Vars
as the type of two "variables" x
and y
data Vars = varX | varY
x + (2 + y)
is captured by
Free (Plus (return varX)
(Free (Plus (Val 2)
(return varY))))
Monadic operations:
return x
is an occurrence of variable x
>>=
is substitutionA simple notion of subtyping between functors:
data (f :+: g) e = Inl (f e) | Inr (g e)
class (Functor sub, Functor sup) => (:<:) sub sup where
inj :: sub a -> sup a
instance (Functor f, Functor g, Functor h, f :<: g) => f :<: (g :+: h) where
inj = Inl
instance (Functor f, Functor g, Functor h, f :<: h) => f :<: (g :+: h) where
inj = Inr
Not real Haskell: original version has restrictions
See also Wadler 2008 (blog), Bahr 2014 (slides)
m
as the target monad
A handler for the effect f
is a function of type:
forall a. f (m a) -> m a
m = IO
as targetclass Functor f => Handler f where
handler :: forall a. f (IO a) -> IO a
Teletype
+ FileSystem
Effects
data Teletype a =
GetChar (Char -> a)
| PutChar Char a
deriving Functor
data FileSystem a =
ReadFile FilePath (String -> a)
| WriteFile FilePath String a
deriving Functor
Primitives
getChar :: Teletype :<: f => Free f Char
putChar :: Teletype :<: f => Char -> Free f ()
readFile :: FileSystem :<: f => FilePath -> Free f String
writeFile :: FileSystem :<: f => FilePath -> String -> Free f ()
getChar = GetChar Return
putChar c = PutChar c $ Return ()
readFile fp = ReadFile fp Return
writeFile fp s = WriteFile fp s $ Return ()
Teletype
+ FileSystem
Example program: UNIX cat
cat :: FilePath -> Free (Teletype :+: FileSystem) ()
cat fp = readFile fp >>= mapM_ putChar
(Alternative type for the same program)
cat :: (Teletype :<: f , FileSystem :<: f) => FilePath -> Free f ()
Teletype
+ FileSystem
Handlers
instance Handler Teletype where
handler (GetChar f) = Prelude.getChar >>= f
handler (PutChar c m) = Prelude.putChar x >> m
instance Handle FileSystem where
handler (ReadFile fp f) = Prelude.readFile fp >>= f
handler (WriteFile fp s m) = Prelude.writeFile fp s >> m
Handler for the sum of two effects, given the single handlers
instance (Handler f, Handler g) => Handler (f :+: g) where
handler (Inl x) = handler x
handler (Inr y) = handler y
A generic evaluator for effectful programs
handle :: Handler f => Free f a -> IO a
handle (Return a) = return a
handle (Pure xs) = handle (fmap handle xs)
Example: running the cat
program in the IO
monad
main :: IO ()
main = handle cat
Easy to define a new effect!
However, extending the target monad is not considered.
E.g.: with IO
as target monad, how to interpret State s
?
data State s a =
Get (s -> State s a)
| Put s (State s a)
Without unsafe tricks, IO a
cannot manage a state of type s
!
++
Intuitively,
(xs ++ ys) ++ zs
takes |xs| + (|xs| + |ys|)
steps
while
xs ++ (ys ++ zs)
takes |xs| + |ys|
steps.
Consequence: reverse
via ++
is \(O(n^2)\) instead of \(O(n)\).
Free.>>=
Similarly, for Free
(m >>= f) >>= g
is slower than
m >>= (\ x -> f x >>= g)
[Voigtländer 2008] shows examples of affected algorithms.
Higher-order free-monadic programs become problematic!
Use type classes and type families to capture monadic interfaces
class Monad m => Get a m where
get :: m a
class Monad m => Put a m where
put :: a -> m ()
type family State (a :: *) (m :: * -> *) :: Constraint
type instance State a m = (Get a m , Put a m)
class Monad m => Input m where
input :: m String
class Monad m => Output m where
output :: String -> m ()
type family InputOutput (m :: * -> *) :: Constraint
type instance InputOutput m = (Input m , Output m)
UndecidableInstances
Example usage:
inputAmount :: Input m => m (Maybe Amount)
inputAmount = liftM readMaybe input
deposit :: (InputOutput m , Put Amount m) => m ()
deposit = do
x <- untilJust $ do
output "Enter the amount you want to store:"
inputAmount
put x
output "Goodbye!"
monad-classes
: Extensibilitytype family Find (t :: (* -> *) -> (* -> *)) (m :: * -> *) :: Nat where
Find t (t m) = Zero
Find t (p m) = Suc (Find t m)
monad-classes
: ExtensibilityReader
's ask
to any transformer stackclass Monad m => MonadReaderN (n :: Nat) r m where
askN :: Proxy n -> m r
instance Monad m => MonadReaderN Zero r (ReaderT r m) where
askN _ = Trans.ask
instance (MonadTrans t, Monad (t m), MonadReaderN n r m, Monad m) =>
MonadReaderN (Suc n) r (t m) where
askN _ = lift $ askN (Proxy :: Proxy n)
type MonadReader r m = MonadReaderN (Find (ReaderT r) m) r m
ask :: forall m r . MonadReader r m => m r
ask = askN (Proxy :: Proxy (Find (ReaderT r) m))
monad-classes
: ExtensibilityState s
s
to distinguish their rolesmonad-classes
: CanDo
type family CanDo (m :: (* -> *)) (eff :: k) :: Bool
StateT
generalises both ReaderT
and WriterT
Consider the syntactic constructions
Free
, Operational
, Unimo
, Freer
…
instance (Teletype :<: f) => Input (Free f) where
input = getChar
instance (Teletype :<: f) => Output (Free f) where
output = putChar
instance (FileSystem :<: f) => ReadFile (Free f) where
readFile = FileSystem.readFile
instance (FileSystem :<: f) => WriteFile (Free f) where
writeFile = FileSystem.writeFile
cat :: (Output m , ReadFile m) => FilePath -> m ()
cat fp = readFile fp >>= mapM_ output
main :: IO ()
main = handle cat
(Remember that handle :: Handler f => Free f a -> IO a
)
monad-classes
, (finally-tagless), …"Program to an 'interface', not an 'implementation'."
class MonadT t where
lift :: Monad m => m a -> t m a
treturn :: Monad m => a -> t m a
tbind :: Monad m => t m a -> (a -> t m b) -> t m b
The syntactic State
monad
data State s x =
Return x
| Get (s -> State s x)
| Put s (State s x)
instance Monad State where
return = Return
(Get k ) >>= f = Get (\ s -> k s >>= f)
(Put s x) >>= f = Put s (x >>= f)
handle :: State s x -> s -> (s , x)
handle (Return x ) s = (s , x)
handle (Get f ) s = handle (f s) s
handle (Put s x) _ = handle
Programs in the syntactic State monad
get :: State s s
get = Get (\ s -> Return s)
put :: State s ()
put s = Put s (Return ())
increment :: State Int ()
increment = get >>= put . (+1)
State
is not modular!We need a more generic representation
Operational
data Operational f a where
Return :: a -> Operational f a
Then :: forall a. f a -> (a -> Operational f b) -> Operational f b
By Parametricity, Operational f a
is isomorphic to Free f a
data Unimo f a =
Return a
| Free (f (Free f a))
| forall b. Bind (Unimo f b) (b -> Unimo f a)
operational
package adds Bind
internally)Codensity
transformationnewtype Codensity f a = Codensity (forall r. (a -> f r) -> f r)
rep :: Monad m => Codensity m a -> m a
abs :: Monad m => m a -> Codensity m a
If you use Codensity (Free f)
instead of Free f
:
(m >>= f) >>= g
reduces to (almost)
m >>= \ x -> f x >>= g
before m
, f
and g
are evaluated!
Operational
:+:
and :<:
, but
Union r v ::
*
r
is a type-level list of "effect labels"v
is the type of "variables"Member f r ::
Constraint
Interesting optimisation [KiselyovVanDerPloeg 2014]
Recall Operational
:
data Operational f a where
Return :: a -> Operational f a
Then :: forall a. f a -> (a -> Operational f b) -> Operational f b
In Freer
, (a -> Operational f b)
is "reified" as an efficient
heterogeneous sequence of continuations (fast append!)