How to interleave a free monadic DSL with state, but interpret state mid-program? - haskell

I have a situation where I want to interleave a free monadic DSL with state, but interpret the state mid-program. Below is a simplified example with only logging and state. More generally the problem is that we need to perform some effects to obtain the initial state, so it can't be done during the final interpretation (runProgram below). Using tagless final and StateT this is simple. The same is probably true using an extensible effect system like polysemy. I couldn't figure out how to do this using coproducts from Data types à la carte while only interpreting part of the union. Perhaps there's an elegant way using coproducts.
I decided to try using FreeT after seeing similar examples here in Haskell and here in Scala. However, the situation is slightly different: the base monad is their custom DSL, rather than some state monad. As far as I can tell, I need state to be the base in order to be able to “eliminate” it in the middle of the program.
Here’s my broken attempt (full example in this gist):
runProgram :: IO ()
runProgram = iterM interpret program
data Log next = Log String next | Noop next deriving Functor
-- Might be the problem, applicative instance using dummy constructor needed for iterT
instance Applicative Log where pure = Noop
type Program a = FreeT (State Int) (Free Log) a
myLog :: String -> Free Log ()
myLog s = liftF $ Log s ()
interpret :: Log (IO a) -> IO a
interpret = \case
Log s next -> putStrLn s >> next
Noop next -> next
-- Program with only logging, state interpreted in the middle
program :: Free Log ()
program = do
myLog "Before stateful program"
finalState <- eliminateState 3 statefulProgram
myLog $ "Final state: " ++ show finalState
eliminateState :: Int -> Program Int -> Free Log Int
eliminateState initialState = iterT (`evalState` initialState)
-- Combines logging and state, but the state doesn't stick. Why?
statefulProgram :: Program Int
statefulProgram = do
lift $ myLog "In stateful program, modifying state"
liftF $ modify (+1)
updatedState <- liftF get
lift $ myLog ("In stateful program, updated state is: " ++ show updatedState)
return updatedState
The state doesn't stick here, output is:
Before stateful program
In stateful program, modifying state
In stateful program, updated state is: 3
Final state: 3
I suspect there's something fundamentally not sound with this approach and that the bodged together DSL Applicative instance is a symptom of that. But I'm not sure what it is. So two questions:
What is the problem with this particular implementation?
How can this situation be modeled using free monads?

As for
What is the problem with this particular implementation?
The FreeT monad transformer is like an onion, with multiple nested layers of the functor parameter (here, State Int).
The function that is passed to iterT is used to "peel" the functorial layers. The problem is that there's no communication between the successive State Int layers. (`evalState` initialState) is used to run each layer separately, always with the same initial state, always discarding the final state for the layer, as evalState is wont to do.

Answering the narrow question (from your comment) of how to write the handler for StateF. (I’m on my phone, so I’ve compiled this code only in my head, but it should give you the general idea.)
data StateF s a = Get (s -> a) | Put s a deriving Functor
data (f :+: g) a = L (f a) | R (g a) deriving Functor
runState :: Functor f => s -> Free (StateF :+: f) a -> Free f (a, s)
runState s (Pure x) = Pure (x, s)
runState s (Free (L (Get k))) = runState s (k s)
runState _ (Free (L (Put s m))) = runState s m
runState s (Free (R f)) = Free (runState s <$> f)
In the R case, you want to leave this layer of the free monad intact — it’s some unknown non-StateF effect. So we just recursively run the rest of the computation inside the f functor using <$>.
You could probably write this code using iter(M), if you don’t like the explicit recursion, but I think you’d need to use StateT to do that.

Related

What are freer monads?

I heard this term a few times, but I still don't know what exactly is a so-called "Freer Monad". The name makes me think about Free Monads, but I don't see how they are actually related. There is some library I found on hackage: http://hackage.haskell.org/package/freer, but the example out there didn't help me a lot.
I don't understand the idea at all, and therefore I don't see any good usecases for them. I also wonder what advantages they provide over free monads and classic mtl stacks.
I know this is an old thread, but i thought I'd answer it anyway just in case
what [...] is a so-called "Freer Monad"
according to the original paper Freer Monads, More Extensible Effects a "Freer Monad" is essentially a Free Monad without the necessary Functor constraint of a Free Monad.
A free monad is basically the essence of the monadic structure; the "smallest" thing that is still a monad. A very nice practial explanation approach can be found in this article. This article also shows that the "normal" free monad needs a Functor constraint.
However, it is often quite tedious adding the functor constraint in every function (and sometimes maybe even weird to implement), and as it turns out, by "moving the functor functionality" to an argument for the Impure constructor so that the implementing side can alter the type of the output itself (so without a general functor), it is possible to get rid of this constraint. This is done by using GADTs: (example from the Freer Monads paper)
data Free f a = Pure a
| Impure (f (Free f a))
instance Functor f => Monad (Free f) where
becomes
data FFree f a where
Pure :: a → FFree f a
Impure :: f x → (x → FFree f a) → FFree f a
instance Monad (FFree f) where
[...]
Impure fx k’ >>= k = Impure fx (k’ >>> k)
This basically lets the later implementation choose how to perform the fmap operation fixed [pun not intended] to the appropriate "output/wrapped type".
So the fundamental difference is essentially usability and generality.
As there was some confusion: FFree is the Freer monad and corresponds to Eff in the package freer-simple.
good usecases for them
Freer monads, just as well as Free monads lend themselves for constructing DSLs.
consider for example a type
data Lang r where
LReturn :: Var -> Lang Int
LPrint :: IntExpr -> Lang ()
LAssign :: Var -> IntExpr -> Lang ()
LRead :: Var -> Lang Int
this tells me that there are a couple of operations to be performed in Lang: return x print x assign x y read y.
We use GADTs here so that we can also specify what output the individual actions are going to have. This comes in quite handy if we write functions in our DSL, because their output can be tpechecked.
adding some convenience functions (that can acutally be derived):
lReturn :: Member Lang effs
=> Var -> Eff effs Int
lReturn = send . LReturn
lPrint :: Member Lang effs
=> IntExpr -> Eff effs ()
lPrint = send . LPrint
lAssign :: Member Lang effs
=> Var -> IntExpr -> Eff effs ()
lAssign v i = send $ LAssign v i
lRead :: Member Lang effs
=> Var -> Eff effs Int
lRead = send . LRead
(this is already written using freer)
now we can use them like this: (assuming that IntExpr contains Variables and Ints)
someFunctionPrintingAnInt = do
lAssign (Var "a") (IE_Int 12)
lPrint (IE_Var $ Var "a")
these functions now enable you to have a DSL that can be interpreted in different ways. All needed for this is an interpreter with a specific type for effs (which is ~~ a type level list of freer monad "instances)
so freer takes the idea of the freer monads and packs it into an effect system.
this interpreter could look something like this:
runLangPure :: Eff '[Lang] Int -> Either () Int -- [StateMap]
runLangPure program = fst . fst $
run (runWriter (runState empty (runError (reinterpret3 go program))))
where
go :: Lang v -> Eff '[Error (), State StateMap, Writer [String]] v
go (LReturn var) = get >>= go (Eval stmt) >>= tell . []
go (LPrint expr) = do
store <- get
value <- evalM expr
tell [show value]
go (LAssign var expr) = do
value <- evalM expr
--modify state (change var)
go (LRead var) = do
strValue <- getLine
get >>= insert var (stringToInt strValue)
the run... part specifies the initial "state" of the monads. the go part is the interpreter itself, interpreting the different possible actions.
Note that one can use the functions get and tell in the same do block even though they are part of different monads, which brings us to
I also wonder what advantages do they provide over free monads and classic mtl stacks.
the implementation allows to use monadic actions of different parts of the "monad stack" without lifting.
About the implementation:
To understand this, we look at it from a high level of abstraction:
the auxiliary functions of our DSL are send to Eff effs where it is required that Member Lang effs.
So the Member constraint is just a way of declaing that Lang is in the type-level list effs in Member Lang effs. (basically typelevel elem)
The Eff monad has the functionality to "ask" the Members of the type level list of monads whether they can handle the current value (remeber, the operations are just values that are intrepreted subsequently). if so their intrepretation is executed, if not, the question is handed off to the next monad in the list.
This becomes more intuitive and understandable when spending some time in the freer-simple code base.

Making Read-Only functions for a State in Haskell

I often end up in a situation where it's very convenient to be using the State monad, due to having a lot of related functions that need to operate on the same piece of data in a semi-imperative way.
Some of the functions need to read the data in the State monad, but will never need to change it. Using the State monad as usual in these functions works just fine, but I can't help but feel that I've given up Haskell's inherent safety and replicated a language where any function can mutate anything.
Is there some type-level thing that I can do to ensure that these functions can only read from the State, and never write to it?
Current situation:
iWriteData :: Int -> State MyState ()
iWriteData n = do
state <- get
put (doSomething n state)
-- Ideally this type would show that the state can't change.
iReadData :: State MyState Int
iReadData = do
state <- get
return (getPieceOf state)
bigFunction :: State MyState ()
bigFunction = do
iWriteData 5
iWriteData 10
num <- iReadData -- How do we know that the state wasn't modified?
iWRiteData num
Ideally iReadData would probably have the type Reader MyState Int, but then it doesn't play nicely with the State. Having iReadData be a regular function seems to be the best bet, but then I have to go through the gymnastics of explicitly extracting and passing it the state every time it's used. What are my options?
It's not hard to inject the Reader monad into State:
read :: Reader s a -> State s a
read a = gets (runReader a)
then you could say
iReadData :: Reader MyState Int
iReadData = do
state <- ask
return (getPieceOf state)
and call it as
x <- read $ iReadData
this would allow you to build up Readers into larger read-only sub-programs and inject them into State only where you need to combine them with mutators.
It's not hard to extend this to a ReaderT and StateT at the top of your monad transformer stack (in fact, the definition above works exactly for this case, just change the type). Extending it to a ReaderT and StateT in the middle of the stack is harder. You basically need a function
lift1 :: (forall a. m0 a -> m1 a) -> t m0 a -> t m1 a
for every monad transformer t in the stack above the ReaderT/StateT, which isn't part of the standard library.
I would recommend wrapping up the State monad in a newtype and defining a MonadReader instance for it:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
import Control.Applicative
import Control.Monad.State
import Control.Monad.Reader
data MyState = MyState Int deriving Show
newtype App a = App
{ runApp' :: State MyState a
} deriving
( Functor
, Applicative
, Monad
, MonadState MyState
)
runApp :: App a -> MyState -> (a, MyState)
runApp app = runState $ runApp' app
instance MonadReader MyState App where
ask = get
local f m = App $ fmap (fst . runApp m . f) $ get
iWriteData :: MonadState MyState m => Int -> m ()
iWriteData n = do
MyState s <- get
put $ MyState $ s + n
iReadData :: MonadReader MyState m => m Int
iReadData = do
MyState s <- ask
return $ s * 2
bigFunction :: App ()
bigFunction = do
iWriteData 5
iWriteData 10
num <- iReadData
iWriteData num
This is certainly more code that #jcast's solution, but it follows the the tradition of implementing your transformer stack as a newtype wrapper, and by sticking with constraints instead of solidified types you can make strong guarantees about the use of your code while providing maximum flexibility for re-use. Anyone using your code would be able to extend your App with transformers of their own while still using iReadData and iWriteData as intended. You also don't have to wrap every call to a Reader monad with a read function, the MonadReader MyState functions are seamlessly integrated with functions in the App monad.
Excellent answers by jcast and bhelkir, with exactly the first idea I thought of—embedding Reader inside State.
I think it's worthwhile to address this semi-side point of your question:
Using the State monad as usual in these functions works just fine, but I can't help but feel that I've given up Haskell's inherent safety and replicated a language where any function can mutate anything.
That's a potential red flag, indeed. I've always found that State works best for code with "small" states that can be contained within the lifetime of a single, brief application of runState. My go-to example is numbering the elements of a Traversable data structure:
import Control.Monad.State
import Data.Traversable (Traversable, traverse)
tag :: (Traversable t, Enum s) => s -> t a -> t (s, a)
tag i ta = evalState (traverse step ta) init
where step a = do s <- postIncrement
return (s, a)
postIncrement :: Enum s => State s s
postIncrement = do result <- get
put (succ result)
return result
You don't directly say so, but you make it sound you may have a big state value, with many different fields being used in many different ways within a long-lived runState call. And perhaps it does need to be that way for your program at this point. But one technique for coping with this might be to write your smaller State actions so that they only use narrower state types than the "big" one and then embed these into the larger State type with a function like this:
-- | Extract a piece of the current state and run an action that reads
-- and modifies only that piece.
substate :: (s -> s') -> (s' -> s -> s) -> State s' a -> State s a
substate extract replace action =
do s <- get
let (s', a) = runState action (extract s)
put (replace s' s)
return a
Schematic example
example :: State (A, B) Whatever
example = do foo <- substate fst (,b) action1
bar <- substate snd (a,) action2
return $ makeWhatever foo bar
-- Can only touch the `A` component of the state
action1 :: State A Foo
action1 = ...
-- Can only touch the `B` component of the state
action2 :: State B Bar
action2 = ...
Note that the extract and replace functions constitute a lens, and there are libraries for that, which may even already include a function like this.

Monad with no wrapped value?

Most of the monad explanations use examples where the monad wraps a value. E.g. Maybe a, where the a type variable is what's wrapped. But I'm wondering about monads that never wrap anything.
For a contrived example, suppose I have a real-world robot that can be controlled, but has no sensors. Maybe I'd like to control it like this:
robotMovementScript :: RobotMonad ()
robotMovementScript = do
moveLeft 10
moveForward 25
rotate 180
main :: IO ()
main =
liftIO $ runRobot robotMovementScript connectToRobot
In our imaginary API, connectToRobot returns some kind of handle to the physical device. This connection becomes the "context" of the RobotMonad. Because our connection to the robot can never send a value back to us, the monad's concrete type is always RobotMonad ().
Some questions:
Does my contrived example seem right?
Am I understanding the idea of a monad's "context" correctly? Am I correct to describe the robot's connection as the context?
Does it make sense to have a monad--such as RobotMonad--that never wraps a value? Or is this contrary to the basic concept of monads?
Are monoids a better fit for this kind of application? I can imagine concatenating robot control actions with <>. Though do notation seems more readable.
In the monad's definition, would/could there be something that ensures the type is always RobotMonad ()?
I've looked at Data.Binary.Put as an example. It appears to be similar (or maybe identical?) to what I'm thinking of. But it also involves the Writer monad and the Builder monoid. Considering those added wrinkles and my current skill level, I think the Put monad might not be the most instructive example.
Edit
I don't actually need to build a robot or an API like this. The example is completely contrived. I just needed an example where there would never be a reason to pull a value out of the monad. So I'm not asking for the easiest way to solve the robot problem. Rather, this thought experiment about monads without inner values is an attempt to better understand monads generally.
TL;DR Monad without its wrapped value isn't very special and you get all the same power modeling it as a list.
There's a thing known as the Free monad. It's useful because it in some sense is a good representer for all other monads---if you can understand the behavior of the Free monad in some circumstance you have a good insight into how Monads generally will behave there.
It looks like this
data Free f a = Pure a
| Free (f (Free f a))
and whenever f is a Functor, Free f is a Monad
instance Functor f => Monad (Free f) where
return = Pure
Pure a >>= f = f a
Free w >>= f = Free (fmap (>>= f) w)
So what happens when a is always ()? We don't need the a parameter anymore
data Freed f = Stop
| Freed (f (Freed f))
Clearly this cannot be a Monad anymore as it has the wrong kind (type of types).
Monad f ===> f :: * -> *
Freed f :: *
But we can still define something like Monadic functionality onto it by getting rid of the a parts
returned :: Freed f
returned = Stop
bound :: Functor f -- compare with the Monad definition
=> Freed f -> Freed f -- with all `a`s replaced by ()
-> Freed f
bound Stop k = k Pure () >>= f = f ()
bound (Freed w) k = Free w >>= f =
Freed (fmap (`bound` k) w) Free (fmap (>>= f) w)
-- Also compare with (++)
(++) [] ys = ys
(++) (x:xs) ys = x : ((++) xs ys)
Which looks to be (and is!) a Monoid.
instance Functor f => Monoid (Freed f) where
mempty = returned
mappend = bound
And Monoids can be initially modeled by lists. We use the universal property of the list Monoid where if we have a function Monoid m => (a -> m) then we can turn a list [a] into an m.
convert :: Monoid m => (a -> m) -> [a] -> m
convert f = foldr mappend mempty . map f
convertFreed :: Functor f => [f ()] -> Freed f
convertFreed = convert go where
go :: Functor f => f () -> Freed f
go w = Freed (const Stop <$> w)
So in the case of your robot, we can get away with just using a list of actions
data Direction = Left | Right | Forward | Back
data ActionF a = Move Direction Double a
| Rotate Double a
deriving ( Functor )
-- and if we're using `ActionF ()` then we might as well do
data Action = Move Direction Double
| Rotate Double
robotMovementScript = [ Move Left 10
, Move Forward 25
, Rotate 180
]
Now when we cast it to IO we're clearly converting this list of directions into a Monad and we can see that as taking our initial Monoid and sending it to Freed and then treating Freed f as Free f () and interpreting that as an initial Monad over the IO actions we want.
But it's clear that if you're not making use of the "wrapped" values then you're not really making use of Monad structure. You might as well just have a list.
I'll try to give a partial answer for these parts:
Does it make sense to have a monad--such as RobotMonad--that never wraps a value? Or is this contrary to the basic concept of monads?
Are monoids a better fit for this kind of application? I can imagine concatenating robot control actions with <>. Though do notation seems more readable.
In the monad's definition, would/could there be something that ensures the type is always RobotMonad ()?
The core operation for monads is the monadic bind operation
(>>=) :: (Monad m) => m a -> (a -> m b) -> m b
This means that an action depends (or can depend) on the value of a previous action. So if you have a concept that inherently doesn't sometimes carry something that could be considered as a value (even in a complex form such as the continuation monad), monad isn't a good abstraction.
If we abandon >>= we're basically left with Applicative. It also allows us to compose actions, but their combinations can't depend on the values of preceding ones.
There is also an Applicative instance that carries no values, as you suggested: Data.Functor.Constant. Its actions of type a are required to be a monoid so that they can be composed together. This seems like the closest concept to your idea. And of course instead of Constant we could use a Monoid directly.
That said, perhaps simpler solution is to have a monad RobotMonad a that does carry a value (which would be essentially isomorphic to the Writer monad, as already mentioned). And declare runRobot to require RobotMonad (), so it'd be possible to execute only scripts with no value:
runRobot :: RobotMonad () -> RobotHandle -> IO ()
This would allow you to use the do notation and work with values inside the robot script. Even if the robot has no sensors, being able to pass values around can be often useful. And extending the concept would allow you to create a monad transformer such as RobotMonadT m a (resembling WriterT) with something like
runRobotT :: (Monad m) => RobotMonadT m () -> RobotHandle -> IO (m ())
or perhaps
runRobotT :: (MonadIO m) => RobotMonadT m () -> RobotHandle -> m ()
which would be a powerful abstraction that'd allow you to combine robotic actions with an arbitrary monad.
Well there is
data Useless a = Useless
instance Monad Useless where
return = const Useless
Useless >>= f = Useless
but as I indicated, that isn't usefull.
What you want is the Writer monad, which wraps up a monoid as a monad so you can use do notation.
Well it seems like you have a type that supports just
(>>) :: m a -> m b -> m b
But you further specify that you only want to be able to use m ()s. In this case I'd vote for
foo = mconcat
[ moveLeft 10
, moveForward 25
, rotate 180]
As the simple solution. The alternative is to do something like
type Robot = Writer [RobotAction]
inj :: RobotAction -> Robot ()
inj = tell . (:[])
runRobot :: Robot a -> [RobotAction]
runRobot = snd . runWriter
foo = runRobot $ do
inj $ moveLeft 10
inj $ moveForward 25
inj $ rotate 180
Using the Writer monad.
The problem with not wrapping the value is that
return a >>= f === f a
So suppose we had some monad that ignored the value, but contained other interesting information,
newtype Robot a = Robot {unRobot :: [RobotAction]}
addAction :: RobotAction -> Robot a -> Robot b
f a = Robot [a]
Now if we ignore the value,
instance Monad Robot where
return = const (Robot [])
a >>= f = a -- never run the function
Then
return a >>= f /= f a
so we don't have a monad. So if you want to the monad to have any interesting states, have == return false, then you need to store that value.

What general structure does this type have?

While hacking something up earlier, I created the following code:
newtype Callback a = Callback { unCallback :: a -> IO (Callback a) }
liftCallback :: (a -> IO ()) -> Callback a
liftCallback f = let cb = Callback $ \x -> (f x >> return cb) in cb
runCallback :: Callback a -> IO (a -> IO ())
runCallback cb =
do ref <- newIORef cb
return $ \x -> readIORef ref >>= ($ x) . unCallback >>= writeIORef ref
Callback a represents a function that handles some data and returns a new callback that should be used for the next notification. A callback which can basically replace itself, so to speak. liftCallback just lifts a normal function to my type, while runCallback uses an IORef to convert a Callback to a simple function.
The general structure of the type is:
data T m a = T (a -> m (T m a))
It looks much like this could be isomorphic to some well-known mathematical structure from category theory.
But what is it? Is it a monad or something? An applicative functor? A transformed monad? An arrow, even? Is there a search engine similar Hoogle that lets me search for general patterns like this?
The term you are looking for is free monad transformer. The best place to learn how these work is to read the "Coroutine Pipelines" article in issue 19 of The Monad Reader. Mario Blazevic gives a very lucid description of how this type works, except he calls it the "Coroutine" type.
I wrote up his type in the transformers-free package and then it got merged into the free package, which is its new official home.
Your Callback type is isomorphic to:
type Callback a = forall r . FreeT ((->) a) IO r
To understand free monad transformers, you need to first understand free monads, which are just abstract syntax trees. You give the free monad a functor which defines a single step in the syntax tree, and then it creates a Monad from that Functor that is basically a list of those types of steps. So if you had:
Free ((->) a) r
That would be a syntax tree that accepts zero or more as as input and then returns a value r.
However, usually we want to embed effects or make the next step of the syntax tree dependent on some effect. To do that, we simply promote our free monad to a free monad transformer, which interleaves the base monad between syntax tree steps. In the case of your Callback type, you are interleaving IO in between each input step, so your base monad is IO:
FreeT ((->) a) IO r
The nice thing about free monads is that they are automatically monads for any functor, so we can take advantage of this to use do notation to assemble our syntax tree. For example, I can define an await command that will bind the input within the monad:
import Control.Monad.Trans.Free
await :: (Monad m) => FreeT ((->) a) m a
await = liftF id
Now I have a DSL for writing Callbacks:
import Control.Monad
import Control.Monad.Trans.Free
printer :: (Show a) => FreeT ((->) a) IO r
printer = forever $ do
a <- await
lift $ print a
Notice that I never had to define the necessary Monad instance. Both FreeT f and Free f are automatically Monads for any functor f, and in this case ((->) a) is our functor, so it automatically does the right thing. That's the magic of category theory!
Also, we never had to define a MonadTrans instance in order to use lift. FreeT f is automatically a monad transformer, given any functor f, so it took care of that for us, too.
Our printer is a suitable Callback, so we can feed it values just by deconstructing the free monad transformer:
feed :: [a] -> FreeT ((->) a) IO r -> IO ()
feed as callback = do
x <- runFreeT callback
case x of
Pure _ -> return ()
Free k -> case as of
[] -> return ()
b:bs -> feed bs (k b)
The actual printing occurs when we bind runFreeT callback, which then gives us the next step in the syntax tree, which we feed the next element of the list.
Let's try it:
>>> feed [1..5] printer
1
2
3
4
5
However, you don't even need to write all this up yourself. As Petr pointed out, my pipes library abstracts common streaming patterns like this for you. Your callback is just:
forall r . Consumer a IO r
The way we'd define printer using pipes is:
printer = forever $ do
a <- await
lift $ print a
... and we can feed it a list of values like so:
>>> runEffect $ each [1..5] >-> printer
1
2
3
4
5
I designed pipes to encompass a very large range of streaming abstractions like these in such a way that you can always use do notation to build each streaming component. pipes also comes with a wide variety of elegant solutions for things like state and error handling, and bidirectional flow of information, so if you formulate your Callback abstraction in terms of pipes, you tap into a ton of useful machinery for free.
If you want to learn more about pipes, I recommend you read the tutorial.
The general structure of the type looks to me like
data T (~>) a = T (a ~> T (~>) a)
where (~>) = Kleisli m in your terms (an arrow).
Callback itself doesn't look like an instance of any standard Haskell typeclass I can think of, but it is a Contravariant Functor (also known as Cofunctor, misleadingly as it turns out). As it is not included in any of the libraries that come with GHC, there exist several definitions of it on Hackage (use this one), but they all look something like this:
class Contravariant f where
contramap :: (b -> a) -> f a -> f b
-- c.f. fmap :: (a -> b) -> f a -> f b
Then
instance Contravariant Callback where
contramap f (Callback k) = Callback ((fmap . liftM . contramap) f (f . k))
Is there some more exotic structure from category theory that Callback possesses? I don't know.
I think that this type is very close to what I have heard called a 'Circuit', which is a type of arrow. Ignoring for a moment the IO part (as we can have this just by transforming a Kliesli arrow) the circuit transformer is:
newtype CircuitT a b c = CircuitT { unCircuitT :: a b (c, CircuitT a b c) }
This is basicall an arrow that returns a new arrow to use for the next input each time. All of the common arrow classes (including loop) can be implemented for this arrow transformer as long as the base arrow supports them. Now, all we have to do to make it notionally the same as the type you mention is to get rid of that extra output. This is easily done, and so we find:
Callback a ~=~ CircuitT (Kleisli IO) a ()
As if we look at the right hand side:
CircuitT (Kleisli IO) a () ~=~
(Kliesli IO) a ((), CircuitT (Kleisli IO) a ()) ~=~
a -> IO ((), CircuitT (Kliesli IO) a ())
And from here, you can see how this is similar to Callback a, except we also output a unit value. As the unit value is in a tuple with something else anyway, this really doesn't tell us much, so I would say they're basically the same.
N.B. I used ~=~ for similar but not entirely equivalent to, for some reason. They are very closely similar though, in particular note that we could convert a Callback a into a CircuitT (Kleisli IO) a () and vice-versa.
EDIT: I would also fully agree with the ideas that this is A) a monadic costream (monadic operation expecitng an infinite number of values, I think this means) and B) a consume-only pipe (which is in many ways very similar to the circuit type with no output, or rather output set to (), as such a pipe could also have had output).
Just an observation, your type seems quite related to Consumer p a m appearing in the pipes library (and probably other similar librarties as well):
type Consumer p a = p () a () C
-- A Pipe that consumes values
-- Consumers never respond.
where C is an empty data type and p is an instance of Proxy type class. It consumes values of type a and never produces any (because its output type is empty).
For example, we could convert a Callback into a Consumer:
import Control.Proxy
import Control.Proxy.Synonym
newtype Callback m a = Callback { unCallback :: a -> m (Callback m a) }
-- No values produced, hence the polymorphic return type `r`.
-- We could replace `r` with `C` as well.
consumer :: (Proxy p, Monad m) => Callback m a -> () -> Consumer p a m r
consumer c () = runIdentityP (run c)
where
run (Callback c) = request () >>= lift . c >>= run
See the tutorial.
(This should have been rather a comment, but it's a bit too long.)

What is the purpose of the reader monad?

The reader monad is so complex and seems to be useless. In an imperative language like Java or C++, there is no equivalent concept for the reader monad, if I am not mistaken.
Can you give me a simple example and clear this up a little bit?
Don't be scared! The reader monad is actually not so complicated, and has real easy-to-use utility.
There are two ways of approaching a monad: we can ask
What does the monad do? What operations is it equipped with? What is it good for?
How is the monad implemented? From where does it arise?
From the first approach, the reader monad is some abstract type
data Reader env a
such that
-- Reader is a monad
instance Monad (Reader env)
-- and we have a function to get its environment
ask :: Reader env env
-- finally, we can run a Reader
runReader :: Reader env a -> env -> a
So how do we use this? Well, the reader monad is good for passing (implicit) configuration information through a computation.
Any time you have a "constant" in a computation that you need at various points, but really you would like to be able to perform the same computation with different values, then you should use a reader monad.
Reader monads are also used to do what the OO people call dependency injection. For example, the negamax algorithm is used frequently (in highly optimized forms) to compute the value of a position in a two player game. The algorithm itself though does not care what game you are playing, except that you need to be able to determine what the "next" positions are in the game, and you need to be able to tell if the current position is a victory position.
import Control.Monad.Reader
data GameState = NotOver | FirstPlayerWin | SecondPlayerWin | Tie
data Game position
= Game {
getNext :: position -> [position],
getState :: position -> GameState
}
getNext' :: position -> Reader (Game position) [position]
getNext' position
= do game <- ask
return $ getNext game position
getState' :: position -> Reader (Game position) GameState
getState' position
= do game <- ask
return $ getState game position
negamax :: Double -> position -> Reader (Game position) Double
negamax color position
= do state <- getState' position
case state of
FirstPlayerWin -> return color
SecondPlayerWin -> return $ negate color
Tie -> return 0
NotOver -> do possible <- getNext' position
values <- mapM ((liftM negate) . negamax (negate color)) possible
return $ maximum values
This will then work with any finite, deterministic, two player game.
This pattern is useful even for things that are not really dependency injection. Suppose you work in finance, you might design some complicated logic for pricing an asset (a derivative say), which is all well and good and you can do without any stinking monads. But then, you modify your program to deal with multiple currencies. You need to be able to convert between currencies on the fly. Your first attempt is to define a top level function
type CurrencyDict = Map CurrencyName Dollars
currencyDict :: CurrencyDict
to get spot prices. You can then call this dictionary in your code....but wait! That won't work! The currency dictionary is immutable and so has to be the same not only for the life of your program, but from the time it gets compiled! So what do you do? Well, one option would be to use the Reader monad:
computePrice :: Reader CurrencyDict Dollars
computePrice
= do currencyDict <- ask
--insert computation here
Perhaps the most classic use-case is in implementing interpreters. But, before we look at that, we need to introduce another function
local :: (env -> env) -> Reader env a -> Reader env a
Okay, so Haskell and other functional languages are based on the lambda calculus. Lambda calculus has a syntax that looks like
data Term = Apply Term Term | Lambda String Term | Var Term deriving (Show)
and we want to write an evaluator for this language. To do so, we will need to keep track of an environment, which is a list of bindings associated with terms (actually it will be closures because we want to do static scoping).
newtype Env = Env ([(String, Closure)])
type Closure = (Term, Env)
When we are done, we should get out a value (or an error):
data Value = Lam String Closure | Failure String
So, let's write the interpreter:
interp' :: Term -> Reader Env Value
--when we have a lambda term, we can just return it
interp' (Lambda nv t)
= do env <- ask
return $ Lam nv (t, env)
--when we run into a value, we look it up in the environment
interp' (Var v)
= do (Env env) <- ask
case lookup (show v) env of
-- if it is not in the environment we have a problem
Nothing -> return . Failure $ "unbound variable: " ++ (show v)
-- if it is in the environment, then we should interpret it
Just (term, env) -> local (const env) $ interp' term
--the complicated case is an application
interp' (Apply t1 t2)
= do v1 <- interp' t1
case v1 of
Failure s -> return (Failure s)
Lam nv clos -> local (\(Env ls) -> Env ((nv, clos) : ls)) $ interp' t2
--I guess not that complicated!
Finally, we can use it by passing a trivial environment:
interp :: Term -> Value
interp term = runReader (interp' term) (Env [])
And that is it. A fully functional interpreter for the lambda calculus.
The other way to think about this is to ask: How is it implemented? The answer is that the reader monad is actually one of the simplest and most elegant of all monads.
newtype Reader env a = Reader {runReader :: env -> a}
Reader is just a fancy name for functions! We have already defined runReader so what about the other parts of the API? Well, every Monad is also a Functor:
instance Functor (Reader env) where
fmap f (Reader g) = Reader $ f . g
Now, to get a monad:
instance Monad (Reader env) where
return x = Reader (\_ -> x)
(Reader f) >>= g = Reader $ \x -> runReader (g (f x)) x
which is not so scary. ask is really simple:
ask = Reader $ \x -> x
while local isn't so bad:
local f (Reader g) = Reader $ \x -> runReader g (f x)
Okay, so the reader monad is just a function. Why have Reader at all? Good question. Actually, you don't need it!
instance Functor ((->) env) where
fmap = (.)
instance Monad ((->) env) where
return = const
f >>= g = \x -> g (f x) x
These are even simpler. What's more, ask is just id and local is just function composition with the order of the functions switched!
I remember being puzzled as you were, until I discovered on my own that variants of the Reader monad are everywhere. How did I discover it? Because I kept writing code that turned out to be small variations on it.
For example, at one point I was writing some code to deal with historical values; values that change over time. A very simple model of this is functions from points of time to the value at that point in time:
import Control.Applicative
-- | A History with timeline type t and value type a.
newtype History t a = History { observe :: t -> a }
instance Functor (History t) where
-- Apply a function to the contents of a historical value
fmap f hist = History (f . observe hist)
instance Applicative (History t) where
-- A "pure" History is one that has the same value at all points in time
pure = History . const
-- This applies a function that changes over time to a value that also
-- changes, by observing both at the same point in time.
ff <*> fx = History $ \t -> (observe ff t) (observe fx t)
instance Monad (History t) where
return = pure
ma >>= f = History $ \t -> observe (f (observe ma t)) t
The Applicative instance means that if you have employees :: History Day [Person] and customers :: History Day [Person] you can do this:
-- | For any given day, the list of employees followed by the customers
employeesAndCustomers :: History Day [Person]
employeesAndCustomers = (++) <$> employees <*> customers
I.e., Functor and Applicative allow us to adapt regular, non-historical functions to work with histories.
The monad instance is most intuitively understood by considering the function (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c. A function of type a -> History t b is a function that maps an a to a history of b values; for example, you could have getSupervisor :: Person -> History Day Supervisor, and getVP :: Supervisor -> History Day VP. So the Monad instance for History is about composing functions like these; for example, getSupervisor >=> getVP :: Person -> History Day VP is the function that gets, for any Person, the history of VPs that they've had.
Well, this History monad is actually exactly the same as Reader. History t a is really the same as Reader t a (which is the same as t -> a).
Another example: I've been prototyping OLAP designs in Haskell recently. One idea here is that of a "hypercube," which is a mapping from intersections of a set of dimensions to values. Here we go again:
newtype Hypercube intersection value = Hypercube { get :: intersection -> value }
One common of operation on hypercubes is to apply a multi-place scalar functions to corresponding points of a hypercube. This we can get by defining an Applicative instance for Hypercube:
instance Functor (Hypercube intersection) where
fmap f cube = Hypercube (f . get cube)
instance Applicative (Hypercube intersection) where
-- A "pure" Hypercube is one that has the same value at all intersections
pure = Hypercube . const
-- Apply each function in the #ff# hypercube to its corresponding point
-- in #fx#.
ff <*> fx = Hypercube $ \x -> (get ff x) (get fx x)
I just copypasted the History code above and changed names. As you can tell, Hypercube is also just Reader.
It goes on and on. For example, language interpreters also boil down to Reader, when you apply this model:
Expression = a Reader
Free variables = uses of ask
Evaluation environment = Reader execution environment.
Binding constructs = local
A good analogy is that a Reader r a represents an a with "holes" in it, that prevent you from knowing which a we're talking about. You can only get an actual a once you supply a an r to fill in the holes. There are tons of things like that. In the examples above, a "history" is a value that can't be computed until you specify a time, a hypercube is a value that can't be computed until you specify an intersection, and a language expression is a value that can't be computed until you supply the values of the variables. It also gives you an intuition on why Reader r a is the same as r -> a, because such a function is also intuitively an a missing an r.
So the Functor, Applicative and Monad instances of Reader are a very useful generalization for cases where you are modeling anything of the sort "an a that's missing an r," and allow you to treat these "incomplete" objects as if they were complete.
Yet another way of saying the same thing: a Reader r a is something that consumes r and produces a, and the Functor, Applicative and Monad instances are basic patterns for working with Readers. Functor = make a Reader that modifies the output of another Reader; Applicative = connect two Readers to the same input and combine their outputs; Monad = inspect the result of a Reader and use it to construct another Reader. The local and withReader functions = make a Reader that modifies the input to another Reader.
In Java or C++ you may access any variable from anywhere without any problem. Problems appears when your code becomes multi-threaded.
In Haskell you have only two ways to pass the value from one function to another:
You pass the value through one of input parameters of the callable function. Drawbacks are: 1) you can't pass ALL the variables in that way - list of input parameters just blow your mind. 2) in sequence of function calls: fn1 -> fn2 -> fn3, function fn2 may not need parameter which you pass from fn1 to fn3.
You pass the value in scope of some monad. Drawback is: you have to get firm understanding what Monad conception is. Passing the values around is just one of great deal of applications where you may use the Monads. Actually Monad conception is incredible powerful. Don't be upset, if you didn't get insight at once. Just keep trying, and read different tutorials. The knowledge you'll get will pay off.
The Reader monad just pass the data you want to share between functions. Functions may read that data, but can't change it. That's all that do the Reader monad. Well, almost all. There are also number of functions like local, but for the first time you can stick with asks only.

Resources