Reader Monad - explanation of trivial case - haskell

I have been trying to get to grips with the reader monad and came across this tutorial. In it, the author presents this example:
example2 :: String -> String
example2 context = runReader (greet "James" >>= end) context
where
greet :: String -> Reader String String
greet name = do
greeting <- ask
return $ greeting ++ ", " ++ name
end :: String -> Reader String String
end input = do
isHello <- asks (== "Hello")
return $ input ++ if isHello then "!" else "."
I know that this is a trivial example that shows the mechanics, but I am trying to figure out why it would be better than doing something like:
example3 :: String -> String
example3 = end <*> (greet "James")
where
greet name input = input ++ ", " ++ name
end input = if input == "Hello" then (++ "!") else (++ ".")

Reader isn't often used by itself in real code. As you have observed, it's not really better than just passing an extra argument to your functions. However, as part of a monad transformer it is an excellent way to pass configuration parameters through your application. Usually this is done by adding a MonadReader constraint to any function that needs access to configuration.
Here's an attempt at a more real-world example:
data Config = Config
{ databaseConnection :: Connection
, ... other configuration stuff
}
getUser :: (MonadReader Config m, MonadIO m) => UserKey -> m User
getUser x = do
db <- asks databaseConnection
.... fetch user from database using the connection
then your main would look something like:
main :: IO ()
main = do
config <- .... create the configuration
user <- runReaderT (getUser (UserKey 42)) config
print user

dfeuer, chi and user2297560 are right in that "Reader isn't often used by itself in real code". It is worth noting, though, that there is next to no essential difference between what you do in the second snippet in the question and actually using Reader as a monad: the function functor is just Reader without the wrappers, and the Monad and Applicative instances for both of them are equivalent. By the way, outside of highly polymorphic code1, the typical motivation for using the function Applicative is making code more pointfree. In that case, moderation is highly advisable. For instance, as far as my own taste goes, this...
(&&) <$> isFoo <*> isBar
... is fine (and sometimes it might even read nicer than the pointful spelling), while this...
end <*> greet "James"
... is just confusing.
Footnotes
For instance, as Carl points out in a comment, it and the related instances can be useful in...
[...] places where you have code that's polymorphic in a type constructor and your use case is passing an argument in. This can come up when using the polymorphic types offered by lenses, for instance.

Related

Haskell Reader monad and argument passing

I was following this tutorial https://blog.ssanj.net/posts/2014-09-23-A-Simple-Reader-Monad-Example.html
It has tree functions that is embarrassing to me
tom :: Reader String String
tom = do
env <- ask
return (env ++ " This is tom.")
jerry :: Reader String String
jerry = do
env <- ask
return (env ++ " This is Jerry.")
tomAndJerry :: Reader String String
tomAndJerry = do
t <- tom
j <- jerry
return (t ++ "\n" ++ j)
runJerryRun :: String
runJerryRun = (runReader tomAndJerry) "Who is this?"
These functions receive no arguments but still they access the reader monad, what magic is happening here? What is the intuition behind this?
I reader monad a kind of global?
Each of the first two functions returns its own instance of a Reader monad. Then, you can compose them together (in the third function).
For the sake of the argument, let's replace Reader with IO and do something similar, with none of these functions receiving any argument:
getIntFromFile :: IO Int
getIntFromFile = do
x <- readFile "myfile.txt"
pure $ read x :: Int
getIntFromStdin :: IO Int
getIntFromStdin = do
x <- getLine
pure $ read x :: Int
As you can see, both use the IO monad but they don't share anything in common. However, since they both use the IO monad, you can (and that's the beauty of it) compose them together as follows:
-- | the equivalent of your `tomAndJerry` function
main :: IO ()
main = do
x <- getIntFromFile
y <- getIntFromStdin
print $ x + y
This is exactly the same logic at play with the example from the tutorial, except with Reader instead of IO.
I think one important misunderstanding was addressed by Daniel Wagner in a comment. The Reader is (well, wraps) a function, so it does take arguments. In light of this, I guess your final question
I reader monad a kind of global?
has an answer: yes, in the sense that the reader monad gives you a way to pass an immutable state/environment through chained computations; so it kind of reads the same value everytime it's invoked (via ask) along the chain.
Which in the case of your code means that the two asks (or, equivalently, tom and jerry) both read the same environment, represented by the string "Who is this?".
Imho, this becomes a bit clearer by desugaring the dos:
tom :: Reader String String
tom = ask >>= \env -> return (env ++ " This is Tom.")
jerry :: Reader String String
jerry = ask >>= \env -> return (env ++ " This is Jerry.")
tomAndJerry :: Reader String String
tomAndJerry = tom >>= \t -> jerry >>= \j -> return (t ++ "\n" ++ j)
Here >>= expects a function that returns a monad, but you don't have it, you have the "ordinary" function (e.g. \env -> env ++ " This is Tom."), so you have to use return to wrap the result back into the monad. Then instead of using >>= and return . f, why don't we use fmap f, since we only have to apply a function inside the monad?
Which means that we can go further and simplify by using Functor for tom and jerry and Applicative for tomAndJerry.
tom :: Reader String String
tom = fmap (++ " This is Tom.") ask
jerry :: Reader String String
jerry = fmap (++ " This is Jerry.") ask
tomAndJerry :: Reader String String
tomAndJerry = (\t j -> t ++ "\n" ++ j) <$> tom <*> jerry
Both tom and jerry are asking for the environment, and each of them applies a function to it. Then tomAndJerry is just a way of composing them via a binary function, as pointed out in the accepted answer.
By the way, the language server tells me of asks, which allows to write
tom :: Reader String String
tom = asks (++ " This is Tom.")

Refactoring Haskell when adding IO

I have a concern regarding how far the introduction of IO trickles through a program. Say a function deep within my program is altered to include some IO; how do I isolate this change to not have to also change every function in the path to IO as well?
For instance, in a simplified example:
a :: String -> String
a s = (b s) ++ "!"
b :: String -> String
b s = '!':(fetch s)
fetch :: String -> String
fetch s = reverse s
main = putStrLn $ a "hello"
(fetch here could more realistically be reading a value from a static Map to give as its result)
But say if due to some business logic change, I needed to lookup the value returned by fetch in some database (which I can exemplify here with a call to getLine):
fetch :: String -> IO String
fetch s = do
x <- getLine
return $ s ++ x
So my question is, how to prevent having to rewrite every function call in this chain?
a :: String -> IO String
a s = fmap (\x -> x ++ "!") (b s)
b :: String -> IO String
b s = fmap (\x -> '!':x) (fetch s)
fetch :: String -> IO String
fetch s = do
x <- getLine
return $ s ++ x
main = a "hello" >>= putStrLn
I can see that refactoring this would be much simpler if the functions themselves did not depend on each other. That is fine for a simple example:
a :: String -> String
a s = s ++ "!"
b :: String -> String
b s = '!':s
fetch :: String -> IO String
fetch s = do
x <- getLine
return $ s ++ x
doit :: String -> IO String
doit s = fmap (a . b) (fetch s)
main = doit "hello" >>= putStrLn
but I don't know if that is necessarily practical in more complicated programs.
The only way I've found thus far to really isolate an IO addition like this is to use unsafePerformIO, but, by its very name, I don't want to do that if I can help it. Is there some other way to isolate this change? If the refactoring is substantial, I would start to feel inclined to avoid having to do it (especially under deadlines, etc).
Thanks for any advice!
Here are a few methods I use.
Reduce dependencies on effects by inverting control. (One of the methods you described in your question.) That is, execute the effects outside and pass the results (or functions with those results partially applied) into pure code. Instead of having main → a → b → fetch, have main → fetch and then main → a → b:
a :: String -> String
a f = b f ++ "!"
b :: String -> String
b f = '!' : f
fetch :: String -> IO String
fetch s = do
x <- getLine
return $ s ++ x
main = do
f <- fetch "hello"
putStrLn $ a f
For more complex cases of this, where you need to thread an argument to do this sort of “dependency injection” through many levels, Reader/ReaderT lets you abstract over the boilerplate.
Write pure code that you expect might need effects in monadic style from the start. (Polymorphic over the choice of monad.) Then if you do eventually need effects in that code, you don’t need to change the implementation, only the signature.
a :: (Monad m) => String -> m String
a s = (++ "!") <$> b s
b :: (Monad m) => String -> m String
b s = ('!' :) <$> fetch s
fetch :: (Monad m) => String -> m String
fetch s = pure (reverse s)
Since this code works for any m with a Monad instance (or in fact just Applicative), you can run it directly in IO, or purely with the “dummy” monad Identity:
main = putStrLn =<< a "hello"
main = putStrLn $ runIdentity $ a "hello"
Then as you need more effects, you can use “mtl style” (as #dfeuer’s answer describes) to enable effects on an as-needed basis, or if you’re using the same monad stack everywhere, just replace m with that concrete type, e.g.:
newtype Fetch a = Fetch { unFetch :: IO a }
deriving (Applicative, Functor, Monad, MonadIO)
a :: String -> Fetch String
a s = pure (b s ++ "!")
b :: String -> Fetch String
b s = ('!' :) <$> fetch s
fetch :: String -> Fetch String
fetch s = do
x <- liftIO getLine
return $ s ++ x
main = putStrLn =<< unFetch (a "hello")
The advantage of mtl style is that you can have multiple different implementations of your effects. That makes things like testing & mocking easy, since you can reuse the logic but run it with different “handlers” for production & testing. In fact, you can get even more flexibility (at the cost of some runtime performance) using an algebraic effects library such as freer-effects, which not only lets the caller change how each effect is handled, but also the order in which they’re handled.
Roll up your sleeves and do the refactoring. The compiler will tell you everywhere that needs to be updated anyway. After enough times doing this, you’ll naturally end up recognising when you’re writing code that will require this refactoring later, so you’ll consider effects from the beginning and not run into the problem.
You’re quite right to doubt unsafePerformIO! It’s not just unsafe because it breaks referential transparency, it’s unsafe because it can break type, memory, and concurrency safety as well—you can use it to coerce any type to any other, cause a segfault, or cause deadlocks and concurrency errors that would ordinarily be impossible. You’re telling the compiler that some code is pure, so it’s going to assume it can do all the transformations it does with pure code—such as duplicating, reordering, or even dropping it, which may completely change the correctness and performance of your code.
The main legitimate use cases for unsafePerformIO are things like using the FFI to wrap foreign code (that you know is pure), or doing GHC-specific performance hacks; stay away from it otherwise, since it’s not meant as an “escape hatch” for ordinary code.
First off, the refactoring doesn't tend to be as bad as you might imagine. Once you make the first change, the type checker will point you to the next few, and so on. But suppose you have a reason to suspect from the start that you might need some extra capability to make a function go. A common way to do this (called mtl-style, after the monad transformer library) is to express your needs in a constraint.
class Monad m => MonadFetch m where
fetch :: String -> m String
a :: MonadFetch m => String -> m String
a s = fmap (\x -> x ++ "!") (b s)
b :: MonadFetch m => String -> m String
b s = fmap (\x -> '!':x) (fetch s)
instance MonadFetch IO where
-- fetch :: String -> IO String
fetch s = do
x <- getLine
return $ s ++ x
instance MonadFetch Identity where
-- fetch :: String -> Identity String
fetch = Identity . reverse
You're no longer tied to a particular monad: you just need one that can fetch. Code operating on an arbitrary MonadFetch instance is pure, except that it can fetch.

How to pass HTTP request parameter to quickQuery?

I'm using Happstack to receive some parameters from an HTTP request then pass these parameters to a function that will retrieve data from the database and return this data in the HTTP response as follow:
myFunc :: IO String
myFunc = do r <- look "personId"
conn <- connectODBC "... my connection string ...";
vals <- quickQuery conn ("SELECT Name FROM Person where Id = ?") [(toSql r)];
return (processData vals)
handlers :: ServerPartT IO Response
handlers = do
x <- liftIO (myFunc);
decodeBody (defaultBodyPolicy "/tmp/" 0 1000 1000)
msum [
dir "getData" $ ok $ toResponse x
, ... other handlers ...
]
mainFunc = simpleHTTP nullConf handlers
But when I build the above code I get the following error:
No instance for (HasRqData IO) arising from a use of `look'
In a stmt of a 'do' block: r <- look "personId"
After reading questions on similar issues (like this one) I think I have to include HasRqData constraint somewhere, but I couldn't learn where and how.
As you may have guessed, this is too an issue with monads. There are a handful of them in happstack (HasRqData, among others), so you may well consider it a complicated case.
Let us begin with the innocent-looking look function.
look :: (Functor m, Monad m, HasRqData m) => String -> m String
Indeed, there is a non-trivial constraint HasRqData. Let us ask ourselves: what monads HaveRqData? (It so happens that IO has not!)
class HasRqData m where
...
Instances
HasRqData RqData
(MonadIO m, MonadPlus m) => HasRqData (ServerPartT m)
...
The other instances are derivative of these first two, so, it looks like we have to consider these two options first.
The RqData has limited effects — you can only do look and its derivatives, extracting information from the request at hand. As we want to also have other effects — querying the database, for one, — this is not enough for us.
The ServerPartT m is the general form of the same old friend of ours, ServerPart ≡ ServerPartT IO. It happens that it also HasRqData. This is not a coincidence, but rather an implication of the design of happstack — looks like the authors meant us to use this single monad everywhere, unless we need particular granularity. So, let's give it a try.
myFunc :: ServerPart String
myFunc = do r <- look "personId"
return undefined
This compiles.
Now, we don't even need to lift myFunc in handlers — our previous predicament solved itself. We will need to lift our access to the database though, by the same jar logic we discussed before.
I believe you can figure the details by yourself. In any case, let me know how it works out!

Distributed Process in monad transformer

Im toying with implementing a gossip based cluster membership backend for the so called cloud-haskell or is it Distributed.Process.. anyway Im trying to get away with handeling state without ioref or MVars and instead using a state transformer and putting the Process monad on the bottom, like so:
type ClusterT = StateT ClusterState
type Cluster a = ClusterT Process a
This works fairly well using Control.Distributed.Process.Lifted (https://hackage.haskell.org/package/distributed-process-lifted) allowing you to do something like this:
mystatefulcomp :: Cluster ()
mystatefulcomp = do
msg <- expect :: Cluster String
old_state <- get
say $ "My old state was " ++ (show old_state)
put $ modifyState curr_state msg
mystatefulcomp
main = do
Right transport <- createTransport '127.0.0.1' '3000' (\n -> ('127.0.0.1', n) defaultTCPParameters
node <- newLocalNode transport initRemoteTable
runProcess node (evalStateT mystatefulcomp initialstate)
where initialstate = ClusterState.empty
this works resonably well and allows me to structure my program fairly well, i can keep my state functional and thread it along in the Cluster monad.
This all break tho when i try to use receiveWait and match to receive messages.
lets rewrite statefulcomp to do something else using receiveWait
doSomethingWithString :: String -> Cluster ()
doSomethingWithString str = do
s < get
put $ modifyState s str
mystatefulcomp :: Cluster ()
mystatefulcomp = do
old_state <- get
receiveWait [ match doSomthingWithString ]
new_state <- get
say $ "old state " ++ (show old_state) ++ " new " ++ (show new_state)
This wont work since the match function is of type (a -> Process b) -> Match b but we want it to be of type (a -> Cluster b) -> Match b. And here is where i get out on thin ice. As i understand Control.Distributed.Process.Lifted rexposes Control.Distributed.Process functions lifted into the tansformer stack allowing you to use functions like expect and say but does not rexposes match, matchIf and so on..
Im really struggeling with this trying to find a work around or a way of re implementing match and its friends to the form of MonadProcess m => (a -> m b) -> Match b.
Any insights is apriciated.
edit
So after som fiddeling about I came up with the following
doSomethingWithString :: String -> Cluster ()
doSomethingWithString str = do
s < get
put $ modifyState s str
doSomethingWithInt :: Int -> Cluster ()
...
mystatefulcomp :: Cluster ()
mystatefulcomp = do
old_state <- get
id =<< receiveWait [ match $ return . doSomethingWithString
, match $ return . doSomethingWithInt ]
new_state <- get
say $ "old state " ++ (show old_state) ++ " new " ++ (show new_state)
This works fairly well but I am still curious about how good of a design this is
As Michael Snoyman points out in a series of blog posts (that's 5 links), wrapping StateT around IO is a bad idea. You just stumbled over one instance where that surfaces.
mystatefulcomp :: Cluster ()
mystatefulcomp = do
old_state <- get
receiveWait [ match doSomethingWithString ]
new_state <- get
The problem is what ends up in new_state if doSomethingWithString throws an error. The old_state? Some intermediate state from doSomethingWithString before the exception? You see, the very fact that we are wondering makes this approach no less bad than just storing the state in an IORef or MVar.
Apart from questionable semantics, this can't even be implemented without distributed-process being rewritten to use MonadBaseControl everywhere. This is exactly why distributed-process-lifted fails to deliver, because it just wraps around the primitives from distributed-process.
So, what I would do here instead is to pass around a data Config = Config { clusterState :: MVar ClusterState } environment (Oh look, Process does that, too!). Possibly with ReaderT which interacts with IO in a sane way, plus you can easily lift any number of nested occurences of Process to ReaderT Config Process yourself.
Repeating the message of Michael's blog posts: StateT isn't bad in general (in a pure transformer stack, that is), just for cases where we wrap IO in some way. I encourage you to read those posts, they were very inspiring for me, so here they are again:
https://www.fpcomplete.com/blog/2017/06/readert-design-pattern
https://www.fpcomplete.com/blog/2017/06/understanding-resourcet
https://www.fpcomplete.com/blog/2017/06/tale-of-two-brackets
https://www.fpcomplete.com/blog/2017/07/announcing-new-unliftio-library
https://www.fpcomplete.com/blog/2017/07/the-rio-monad

Monad Transformers vs Passing parameters to functions

I am new to Haskell but understand how Monad Transformers can be used.
Yet, I still have difficulties grabbing their claimed advantage over passing parameters to function calls.
Based on the wiki Monad Transformers Explained, we basically have a Config Object defined as
data Config = Config Foo Bar Baz
and to pass it around, instead of writing functions with this signature
client_func :: Config -> IO ()
we use a ReaderT Monad Transformer and change the signature to
client_func :: ReaderT Config IO ()
pulling the Config is then just a call to ask.
The function call changes from client_func c to runReaderT client_func c
Fine.
But why does this make my application simpler ?
1- I suspect Monad Transformers have an interest when you stitch a lot of functions/modules together to form an application. But this is where is my understanding stops. Could someone please shed some light?
2- I could not find any documentation on how you write a large modular application in Haskell, where modules expose some form of API and hide their implementations, as well as (partly) hide their own States and Environments from the other modules. Any pointers please ?
(Edit: Real World Haskell states that ".. this approach [Monad Transformers] ... scales to bigger programs.", but there is no clear example demonstrating that claim)
EDIT Following Chris Taylor Answer Below
Chris perfectly explains why encapsulating Config, State,etc... in a Transformer Monad provides two benefits:
It prevents a higher level function from having to maintain in its type signature all the parameters required by the (sub)functions it calls but not required for its own use (see the getUserInput function)
and as a consequence makes higher level functions more resilient to a change of the content of the Transformer Monad (say you want to add a Writer to it to provide Logging in a lower level function)
This comes at the cost of changing the signature of all functions so that they run "in" the Transformer Monad.
So question 1 is fully covered. Thank you Chris.
Question 2 is now answered in this SO post
Let's say that we're writing a program that needs some configuration information in the following form:
data Config = C { logFile :: FileName }
One way to write the program is to explicitly pass the configuration around between functions. It would be nice if we only had to pass it to the functions that use it explicitly, but sadly we're not sure if a function might need to call another function that uses the configuration, so we're forced to pass it as a parameter everywhere (indeed, it tends to be the low-level functions that need to use the configuration, which forces us to pass it to all the high-level functions as well).
Let's write the program like that, and then we'll re-write it using the Reader monad and see what benefit we get.
Option 1. Explicit configuration passing
We end up with something like this:
readLog :: Config -> IO String
readLog (C logFile) = readFile logFile
writeLog :: Config -> String -> IO ()
writeLog (C logFile) message = do x <- readFile logFile
writeFile logFile $ x ++ message
getUserInput :: Config -> IO String
getUserInput config = do input <- getLine
writeLog config $ "Input: " ++ input
return input
runProgram :: Config -> IO ()
runProgram config = do input <- getUserInput config
putStrLn $ "You wrote: " ++ input
Notice that in the high level functions we have to pass config around all the time.
Option 2. Reader monad
An alternative is to rewrite using the Reader monad. This complicates the low level functions a bit:
type Program = ReaderT Config IO
readLog :: Program String
readLog = do C logFile <- ask
readFile logFile
writeLog :: String -> Program ()
writeLog message = do C logFile <- ask
x <- readFile logFile
writeFile logFile $ x ++ message
But as our reward, the high level functions are simpler, because we never need to refer to the configuration file.
getUserInput :: Program String
getUserInput = do input <- getLine
writeLog $ "Input: " ++ input
return input
runProgram :: Program ()
runProgram = do input <- getUserInput
putStrLn $ "You wrote: " ++ input
Taking it further
We could re-write the type signatures of getUserInput and runProgram to be
getUserInput :: (MonadReader Config m, MonadIO m) => m String
runProgram :: (MonadReader Config m, MonadIO m) => m ()
which gives us a lot of flexibility for later, if we decide that we want to change the underlying Program type for any reason. For example, if we want to add modifiable state to our program we could redefine
data ProgramState = PS Int Int Int
type Program a = StateT ProgramState (ReaderT Config IO) a
and we don't have to modify getUserInput or runProgram at all - they'll continue to work fine.
N.B. I haven't type checked this post, let alone tried to run it. There may be errors!

Resources