Understanding how reader monad simulates global variables - haskell

From what I understand now the WAY that a monad tries to simulate a global variable is by "storing" the variable (or input) in a function (and the function also is a variable), and storing the function into another function by "passing it"; in the end, all the functions in the chain become a single function that folds multiple smaller functions.
Example:
(+2) >>= \a-> (+3) >>= \b -> return(a+b)
Based on the tutorial, >>= works like this f >>= g = \w -> g (f w) w
so what I understand is we are getting a function that takes two inputs, a w (variable) and a function (that also uses that variable)
and output ((+3) w). Here, w was the input.
So this line:
(+2) >>= \a-> (+3) >>= \b -> return(a+b)
is equivalent to
\w -> (\(2+w) -> (+3) w) >>=\b -> return (a+b)
a
(and this 2+w function been "stored" in (\a->(+3))'s first input \a).
Similarly:
\w2 -> (\b ->return (...)) ( \w -> (\(2+w) -> (+3) w) ) w2
and \b is stored in the \w -> (\(2+w) -> (+3) w):
\w2 -> ( \(( \w -> (\(2+w) -> (+3) w) ) -> return(...)) w2
Then, the return (a+b) is not actually just simply doing return x = \_ -> x, but is also able to take functions (a and b) out of that big function \w2 -> ( \b(a inside) -> return(...)) w2 to get another big function:
( (\w -> 2+w) +(\w -> (\(2+w) -> (+3) w) )
Do I understand it correctly? Or am I entirely wrong. I didn't find any tutorial that talked about return (taking input from function). Monads are still very confusing to me.

Let’s go through your example step by step in two ways. First, let’s see what the do notation equivalent is:
do
a <- (+ 2)
b <- (+ 3)
return (a + b)
This is essentially an abstraction over the following repetitive pattern, where many different functions are all applied to the same shared “environment” value and then there’s some final result returned:
\ env -> let
a = (+ 2) env
b = (+ 3) env
in (a + b)
In fact, for consistency with the other actions, the return also receives the environment, and just ignores it:
\ env -> let
a = (+ 2) env
b = (+ 3) env
in const (a + b) env -- const x y = x
We can make this fit the Monad pattern by having >>= carry this environment along and pass it to each function ((+ 2), (+ 3), const (a + b)).
>>= takes two functions function and continue, where function is one of (+ 2) or (+ 3) above; >>= applies function to the environment, and then passes two things along to continue: the result of function, and the environment again, so that subsequent steps in continue can also read the environment.
-- Type:
(>>=) :: (Monad m) => m a -> (a -> m b) -> m b
-- or:
(>>=) :: (->) env a -> (a -> (->) env b) -> (->) env b
-- or:
(>>=) :: (env -> a) -> (a -> env -> b) -> env -> b
-- Implementation:
instance Monad ((->) env) where
function >>= continue = \ env -> continue (function env) env
-- or:
(>>=) = \ function continue env -> continue (function env) env
In fact, with the {-# LANGUAGE InstanceSigs #-} extension, you can write exactly the last type above as the signature for >>= in the Monad instance, and I recommend using that extension to help you implement typeclasses as you’re learning.
return takes a value x, and produces a function that fits in place of continue above, which, as I mentioned before, just ignores the environment and returns x.
return x = \ _env -> x
-- =
return = \ x _env -> x
-- =
return = const
Now secondly, if we go back to the desugared do notation, and add parentheses to clarify the scope of the lambdas:
(+ 2) >>= (\ a -> (+ 3) >>= (\ b -> return (a + b)))
Then we can inline those definitions of >>= and return to see how they work in this context. I’ve numbered the variables in each substitution to make the scopes a little more explicit.
(\ function1 continue1 env1 -> continue1 (function1 env1) env1)
(+ 2)
(\ a ->
(\ function2 continue2 env2 -> continue2 (function2 env2) env2)
(+ 3)
(\ b ->
(\ x env3 -> x)
(a + b)))
Then we can substitute all the variables throughout, by applying the functions to their arguments (beta-reduction):
let
function1 = (+ 2)
continue1 = \ a ->
let
function2 = (+ 3)
continue2 = \ b ->
let
x = (a + b)
in \ _env3 -> x
in \ env2 -> continue2 (function2 env2) env2
in \ env1 -> continue1 (function1 env1) env1)
-- =
\ env1 ->
(\ a env2 ->
(\ b _env3 -> a + b)
(env2 + 3)
env2)
(env1 + 2)
env1
-- =
\ env1 -> let
a = (env1 + 2)
env2 = env1
in let
b = (env2 + 3)
_env3 = env2
in (a + b)
Then we can omit all the redundant env variables, since they’re all equal to each other, and just used to pass the value along to all the functions:
\ env -> let
a = (env + 2)
b = (env + 3)
in (a + b)
And this is exactly the code we were trying to abstract away!
This is only one Monad instance, though; all other instances work differently based on the specific type involved. What all the basic instances have in common is that they abstract over some common repetitive pattern in pure code, e.g.:
-- State:
\ state1 -> let
(a, state2) = function1 state1
(b, state3) = function2 state2
(c, state4) = function3 state3
…
in (x, stateX)
-- Writer:
\ log1 -> let
(a, log2) = function1
(b, log3) = function2
(c, log4) = function3
…
in (x, log1 <> log2 <> log3 <> log4)
-- Maybe:
case function1 of
Just a -> case function2 of
Just b -> case function3 of
Just c -> …
Just x -> Just x
Nothing -> Nothing
Nothing -> Nothing
Nothing -> Nothing
Nothing -> Nothing
-- Either:
case function1 of
Right a -> case function2 of
Right b -> case function3 of
Right c -> …
Right x -> Right x
Left errorX -> Left errorX
Left error3 -> Left error3
Left error2 -> Left error2
Left error1 -> Left error1
-- List:
concatMap
(\ a -> concatMap
(\ b -> concatMap
(\ c -> concatMap
…
[x])
function3)
function2)
function1
Likewise, the basic monad transformers abstract over such patterns in monadic code.
-- MaybeT:
do
ma <- function1
case ma of
Just a -> do
mb <- function2
case mb of
Just b -> do
mc <- function3
case mc of
Just c -> …
Just x -> pure (Just x)
Nothing -> pure Nothing
Nothing -> pure Nothing
Nothing -> pure Nothing
Nothing -> pure Nothing
Nothing -> pure Nothing
The Monad/Applicative/Functor hierarchy provide a common way for data structures and control structures to abstract over some kind of sequential pattern like this so they can all be used with do notation and library functions like replicateM that work for any Monad.
It helps to look at lots of different examples, not just one instance, to get a feel for what they have in common and how they differ.

In your question, you are describing one specific monad, the "reader" monad. At the level of detail you're trying to understand it, this reader monad will behave differently from other monads.
That said, I think your understanding of the detailed operation of the reader monad is partially correct. However, you've missed a couple of things: you've messed up the precise order of operations in your example expression that's dictated by how lambda expressions are parsed, and you've sort of glossed over the "merge" step that combines the \w -> ... lambdas that are introduced by each >>= operator so they all refer to the same global variable.
To make it a little clearer, let me spell it out in detail, using simple transformations of expressions that match the way GHC would actually evaluate your code...
Let's take your example:
(+2) >>= \a -> (+3) >>= \b -> return (a+b)
and start by inserting some parenthesis. Even though the operator >>= is left associative, lambda expressions like \a -> ... suck up as much valid expression as they can, so the correct placement of parentheses in this expression is:
(+2) >>= ( \a -> ( (+3) >>= ( \b -> return (a+b) ) ) ) -- (1)
Now, as you note, the definition of >>= is:
f >>= g = \w -> g (f w) w
Also, the definition of return is:
return x = \w -> x
so let's work on the expression for the right-most occurrence of >>= in (1):
(+3) >>= ( \b -> return (a+b) )
= -- apply definition of `>>=` with f = (+3); g = \b -> return (a+b)
\w -> (\b -> return (a+b)) ((+3) w) w
= -- apply lambda expression (\b -> ...) to first argument ((+3) w)
\w -> (return (a + (+3) w)) w
= -- apply definition of `return` (with renamed variable w')
\w -> (\w' -> a + (+3) w) w
= -- apply lambda expression (\w' -> ...) to first argument w
\w -> a + (+3) w
So, we have:
(+3) >>= ( \b -> return (a+b) ) === \w -> a + (+3) w -- (2)
and, in a sense, the operator >>= works by passing the function (+3) as the argument b. However, it doesn't literally do this, because the argument b has numeric type, not function type. Instead, it "pulls out" a lambda for the "global variable" \w -> ... and then passes (+3) w as b, which works fine, since (+3) w has a numeric type.
Now, let's look at the original example (1) with the substitution (2):
-- from (1) and the subsitution (2):
(+2) >>= ( \a -> ( \w -> a + (+3) w ) )
= -- apply defn of >>= with f = (+2); g = \a -> (\w -> a + (+3) w)
\w' -> (\a -> (\w -> a + (+3) w)) ((+2) w') w'
= -- apply lambda (\a -> ...) to ((+2) w')
\w' -> (\w -> (+2) w' + (+3) w) w'
= -- apply lambda (\w -> ...) to w'
\w' -> (+2) w' + (+3) w'
and, again, in a sense, the operator >>= works by passing the function (+2) as argument a. Since it can't do it literatlly, it does it by pullling a lambda for the "global variable" \w' -> ... out and passing (+2) w' as a, and then it sort of "merges" the \w -> ... lambda pulled out by the rightmost >>= operator with the \w' -> ... it's added, so they point to the same global variable.
Obviously, if we added additional similar binds on the left:
(+8) >>= \e -> (+1) >>= \o -> (+2) >>= \a -> (+3) >>= \b -> return (e+o+a+b)
we'd get the same pattern of adding a new lambda \w' -> ... for the global variable and then "merging" it with the existing lambda \w -> ...:
\w -> (+8) w + (+1) w + (+2) w + (+3) w

Related

Understanding do notation for simple Reader monad: a <- (*2), b <- (+10), return (a+b)

instance Monad ((->) r) where
return x = \_ -> x
h >>= f = \w -> f (h w) w
import Control.Monad.Instances
addStuff :: Int -> Int
addStuff = do
a <- (*2)
b <- (+10)
return (a+b)
I'm trying to understand this monad by unwiding the do notation, because I think the do notation hides what happens.
If I understood correctly, this is what happens:
(*2) >>= (\a -> (+10) >>= (\b -> return (a+b)))
Now, if we take the rule for >>=, we must understand (*2) as h and (\a -> (+10) >>= (\b -> return (a+b))) as f. Applying h to w is easy, let's just say it is 2w (I don't know if 2w is valid in haskell but just for reasoning lets keep it this way. Now we have to apply f to h w or 2w. Well, f simply returns (+10) >>= (\b -> return (a+b)) for an specific a, which is 2w in our case, so f (hw) is (+10) >>= (\b -> return (2w+b)). We must first get what happens to (+10) >>= (\b -> return (2w + b)) before finally applying it to w.
Now we reidentify (+10) >>= (\b -> return (2w + b)) with our rule, so h is +10 and f is (\b -> return (2w + b)). Let's first do h w. We get w + 10. Now we need to apply f to h w. We get (return (2w + w + 10)).
So (return (2w + w + 10)) is what we need to apply to w in the first >>= that we were tyring to uwind. But I'm totally lost and I don't know what happened.
Am I thinking in the rigth way? This is so confusing. Is there a better way to think of it?
You're forgetting that operator >>= doesn't return just f (h w) w, but rather \w -> f (h w) w. That is, it returns a function, not a number.
By substituting it incorrectly you lost the outermost parameter w, so it's no wonder it remains free in your final expression.
To do this correctly, you have to substitute function bodies for their calls completely, without dropping stuff.
If you substitute the outermost >>=, you will get:
(*2) >>= (\a -> ...)
==
\w -> (\a -> ...) (w*2) w
Then, if you substitute the innermost >>=, you get:
\a -> (+10) >>= (\b -> return (a+b))
==
\a -> \w1 -> (\b -> return (a+b)) (w1 + 10) w1
Note that I use w1 instead of w. This is to avoid name collisions later on when I combine the substitutions, because these two ws come from two different lambda abstractions, so they're different variables.
Finally, substitute the return:
return (a+b)
==
\_ -> a+b
Now insert this last substitution into the previous one:
\a -> (+10) >>= (\b -> return (a+b))
==
\a -> \w1 -> (\b -> return (a+b)) (w1 + 10) w1
==
\a -> \w1 -> (\b -> \_ -> a+b) (w1 + 10) w1
And finally insert this into the very first substitution:
(*2) >>= (\a -> ...)
==
\w -> (\a -> ...) (w*2) w
==
\w -> (\a -> \w1 -> (\b -> \_ -> a+b) (w1 + 10) w1) (w*2) w
And now that all substitutions are compete, we can reduce. Start with applying the innermost lambda \b -> ...:
\w -> (\a -> \w1 -> (\_ -> a+w1+10) w1) (w*2) w
Now apply the new innermost lambda \_ -> ...:
\w -> (\a -> \w1 -> a+w1+10) (w*2) w
Now apply \a -> ...:
\w -> (\w1 -> w*2+w1+10) w
And finally apply the only remaining lambda \w1 -> ...:
\w -> w*2+w+10
And voila! The whole function reduces to \w -> (w*2) + (w+10), completely as expected.
First, we write out the implicit argument in your definition explicitly,
addStuff :: Int -> Int
addStuff = do
a <- (*2)
b <- (+10)
return (a+b)
=
addStuff :: Int -> Int
addStuff x = ( do
a <- (*2)
b <- (+10)
return (a+b) ) x
=
....
Then, with
return x = const x
(f =<< h) w = f (h w) w -- (f =<< h) = (h >>= f)
it should be easier to follow and substitute the definitions, line for line:
....
=
( (*2) >>= (\a -> -- (h >>= f) =
(+10) >>= (\b ->
const (a+b) ) ) ) x
=
( (\a -> -- = (f =<< h)
(+10) >>= (\b ->
const (a+b) ) ) =<< (*2) ) x -- (f =<< h) w =
=
(\a ->
(+10) >>= (\b ->
const (a+b) ) ) ( (*2) x) x -- = f (h w) w
=
( let a = (*2) x in -- parameter binding
(+10) >>= (\b ->
const (a+b) ) ) x
=
let a = (*2) x in -- float the let
((\b ->
const (a+b) ) =<< (+10) ) x -- swap the >>=
=
let a = (*2) x in
(\b -> -- (f =<< h) w =
const (a+b) ) ( (+10) x) x -- = f (h w) w
=
let a = (*2) x in
(let b = (+10) x in -- application
const (a+b) ) x
=
let a = (*2) x in -- do a <- (*2)
let b = (+10) x in -- b <- (+10)
const (a+b) x -- return (a+b)
The essence of reader monad is application to same argument shared between all calls.
Intuitively, each function call on the right-hand side of the <- is given an additional argument, which you can think of as the argument to addStuff itself.
Take
addStuff :: Int -> Int
addStuff = do
a <- (*2)
b <- (+10)
return (a+b)
and turn it into
addStuff :: Int -> Int
addStuff x = let a = (*2) x
b = (+10) x
in (a+b)
It looks a little less "strange" if you use the MonadReader instance for (->) r, which provides ask as a way to get direct access to the implicit value.
import Control.Monad.Reader
addStuff :: Int -> Int
addStuff = do
x <- ask -- ask is literally just id in this case
let a = x * 2
let b = x + 10
return (a + b)

Meaning of different lambda functions and characters

At the moment I am learning Haskell, but I am struggling with the syntax of a few example. What do they exactly mean?
First: What is the difference between these two lambdas (-> \y and y)?
lambda1 = \x -> \y -> x + y
lambda2 = \x y -> x + y
Second: What does this mean? Is this a lambda that act as a "pseudo" list generator that generates a list with 3 elements. How can I create such a list?
lambda3 = [\x -> x+1, \x -> 2*x, \x -> x^2]
Third: What does the \_ exactly mean?
lambda4 = \_ -> (\x -> x+1, \() -> 'a')
lambda2 is syntactic sugar for lambda1. All of these are equivalent:
f = \x -> \y -> x + y
f = \x y -> x + y
f x = \y -> x + y
f x y = x + y
f x y = (+) x y
f x = (+) x
f = (+)
lambda3 is a list of unary functions on numbers. Each function has the type (Num a) => a -> a, so the list has type (Num a) => [a -> a]. You could produce a list of values from this with map or a list comprehension:
fs = [\x -> x+1, \x -> 2*x, \x -> x^2]
map (\f -> f 3) fs
map ($ 3) fs
[f 3 | f <- fs]
==
[4, 6, 9]
lambda4 uses pattern-matching syntax. For example, if you have a data type:
data Foo = Foo Int String
Then you can write a lambda that pattern-matches on it:
f = \ (Foo n s) -> concat (replicate n s)
f (Foo 3 "bar") == "barbarbar"
(But unlike case, there is no way to provide alternative patterns if Foo has multiple constructors.)
The _ pattern just says “accept a value and ignore it”, so lambda4 is a function that accepts an argument, ignores it, and returns a pair (2-tuple) of unary functions, the first of type (Num a) => a -> a and the second of type () -> Char, so its type is Num a => r -> (a -> a, () -> Char).
lambda4 = \_ -> (\x -> x+1, \() -> 'a')
lambda4 = \ignored -> (\x -> x+1, \() -> 'a')
(inc, getA) = lambda4 ()
inc 3 == 4
getA () == 'a'
Functions that ignore their arguments can be constructed with the const function, and operator sections ((+ 1)) are typically preferred over lambdas (\x -> x + 1), so you can also write the above as:
lambda4 = const ((+ 1), const 'a')
On your second question, lambda3 is just a bad variable name. this is a list of functions of type Num a => a -> a. You can verify that by typing the following in ghci:
:t [\x -> x+1, \x -> 2*x, \x -> x^2]
First: What is the difference between these two lambdas (-> \y and y)?
There is no difference. Both produce the same output for the same input, and since they're pure functions, you can be sure that they produce no external effects that you wouldn't see.
The difference lies in that the first lambda uses syntactic sugar for currying.
\x y -> x + y is equal to \x -> \y -> x + y. Now, don't you think it looks a lot like type signatures, such as foo :: Int -> Int -> Int ? ;)
It means that the function foo takes 2 Int and produces an Int.
Since I don't have a very precise answer for the 2nd…
Third: What does the \_ exactly mean?
It's a lambda function (\) to which is associated the _ variable. _ is used as a placeholder to say “I don't care about the content of this variable, I'm even going to give it a proper name”.
There is no -> y. The correct way to read this is
(\ x -> (\ y -> (x + y)))
As it happens, Haskell has "curried functions", which means that
\ x y -> (x + y)
just happens to be equivalent to the above.
lambda3 is a list which contains three elements. Each of those elements happens to be a function. Functions are data in Haskell; you can pass them as arguments, return them as results, stuff them into lists, etc.
lambda3 = [ (\x -> x+1) , (\x -> 2*x) , (\x -> x^2) ]
lambda4 = \_ -> (\x -> x+1, \() -> 'a')
The "_" character basically means "I don't care what this is; ignore it". You can use it anywhere you can use a pattern. For example,
foobar x _ z = x + y
is a 3-argument function that completely ignores argument #2. Read about pattern matching and this should become clear. (I.e., it's not to do with lambdas, it's to do with patterns.)

Understanding Monadic Fibonacci

I am learning haskell and learning monads. I've watched and read various tutorials and coded some simple examples for state monad, however I am not able to understand the following piece of code (taken from Haskell Wiki):
import Control.Monad.State
fib n = flip evalState (0,1) $ do
forM [0..(n-1)] $ \_ -> do
(a,b) <- get
put (b,a+b)
(a,b) <- get
return a
My question boils down to the following:
What is going inside the first statement of the inner do, i.e what does (a,b)<-get result into. What will be the values of a and b for some concrete example.
Why would you want to use the state monad over here?
In this example, the state is a pair containing the previous two numbers generated in the sequence. This is initially (0, 1) provided to evalState.
The type of get is MonadState s m => m s so in the inner do block
(a, b) <- get
fetches the state pair and binds a and b to the first and second elements respectively. The state is then updated in the following put.
The state will therefore be:
(0, 1), (1, 1), (1, 2), (3, 2), (3, 5), ...
The outer
(a, b) <- get
return a
unpacks the final state value and returns the first element.
First lets make clear the Fibonacci algorithm being used. The idea is to start with the tuple (0, 1), then find the next as (1, 0 + 1), the next as (1, 1 + 1), (2, 2 + 1), (3, 3 + 2), and so on. Generally, the step is \(a, b) -> (b, a + b). You can see that in these tuples are the Fibonacci numbers.
What is going inside the first statement of the inner do, i.e what
does (a,b)<-get result into?
Haskell does not have statements, only expressions.
y <- x is not a complete expression. It is similar to x >>= \y ->.
y <- x
m
Is a complete expression and is equivalent to x >>= \y -> m. A line n not of the form y <- n is equivalent to _ <- n (excluding let lines and maybe some others I forget).
Using this we can desugar do-notation.
fib n =
flip evalState (0, 1)
( forM
[0..(n-1)]
(\_ -> get >>= (\(a, b) -> put (b, a + b)))
>>= (\_ -> get >>= (\(a, b) -> return a)))
)
Now it is just about understanding >>=, return, get, put, and so on.
State is actually just functions of the type s -> (s, a). They take an initial state and yield the next state plus some other value.
m >>= n a.k.a. "bind" has the type Monad m => m a -> (a -> m b) -> m b. Then, if our Monad is State s, this is the same as:
m >>= n ::
( s -> (s, a))
-> (a -> s -> (s, b))
-> ( s -> (s, b))
The a returned by m has to be passed to n. What else can we guess? We expect the state to pass along as well, so the state returned by m must be passed to n as well. The function m >>= n must return the state and value that n returns. We then know how to implement bind:
m >>= n = uncurry (flip n) . m
return :: Monad m => a -> m a which is then equivalent to return :: a -> s -> (s, a):
return = flip (,)
get :: State s s is equivalent to get :: s -> (s, s):
get = join (,)
put :: s -> State s () or put :: s -> s -> (s, ()):
put s _ = (s, ())
evalState :: s -> State s a -> a or evalState :: s -> (s -> (s, a)) -> a:
evalState s f = snd (f s)
You can expand all the definitions and see exactly what is happening in the example. Just the intuitions should suffice though.
forM
[0..(n-1)]
(\_ -> get >>= (\(a, b) -> put (b, a + b)))
We don't care about having the numbers 0 to n - 1 so the first argument is dropped. get retrieves the current state, then put writes the new state. We do this n times.
>>= (\_ -> get >>= (\(a, b) -> return a)))
We don't care about the accumulated value (which is unit) and so the first parameter is dropped. Then we get the current state and project just the first element of the pair. This is the final answer we're looking for.
flip evalState (0, 1) …
Finally we run starting from the initial state (0, 1).
There are some cleanups we can make to this implementation. First, we don't care about the range [0..(n-1)], we just care about repeating an action n times. A more direct way to do this is the following:
replicateM n (get >>= \(a, b) -> put (b, a + b))
The result is a list of unit which is unused, so a more efficient version is:
replicateM_ n (get >>= \(a, b) -> put (b, a + b))
There is already a function for the common pattern of get followed by put named modify, which is defined as \f -> get >>= put . f. Therefore:
replicateM_ n (modify (\(a, b) -> (b, a + b)))
Then there is the part:
>>= (\_ -> get >>= (\(a, b) -> return a)))
Any time we don't care about the previous result we can use >>.
>> get >>= (\(a, b) -> return a))
This is:
>> get >>= return . fst
m >>= return . f simplifies to fmap f m:
>> fmap fst get
Now we have, in total:
fib n =
evalState
( replicateM_ n (modify (\(a, b) -> (b, a + b)))
>> fmap fst get
)
(0, 1)
We might also use, for comparison:
fib n =
fst
( evalState
( replicateM_ n (modify (\(a, b) -> (b, a + b)))
>> get
)
(0, 1)
)
And then because I am silly:
fib =
fst
. flip evalState (0, 1)
. (>> get)
. flip replicateM_ (modify (snd &&& uncurry (+)))
Why would you want to use the state monad over here?
You wouldn't. This is clear because we only use the state value; the other value is always unit and discarded. In other words, we only need n (i.e. which Fibonacci number to find) at the beginning and afterwards we only need the accumulated tuple.
Sometimes you think to have a string of compositions like h . g . f but you want to send two arguments through instead of just one. That is when State may be applicable.
If some functions read and some write the state (the second argument), or do both, then State fits the bill. If there are only readers then use Reader and if there are only writers then use Writer.
We can alter the example to make better use of the State Monad. I will make the tuple disappear!
fib =
flip evalState 0
. foldr (=<<) (return 1)
. flip replicate (\x -> get >>= \y -> put x $> x + y)
So the docs state: get :: m s -- Return the state from the internals of the monad (see here).
But I remember very well that when I tried to wrap my head around the State Monad this didn't help me a lot.
I can only recommend playing around with :i and :t in ghci and test out different sub-expressions. Just to get a feel for it. A bit like this:
import Control.Monad.State.Lazy
runState (get) 0
runState (get >>= \x -> put (x+1)) 0
:t return 1 :: State Int Int
runState (return 1) 0
runState (return 1 >>= \x -> (get >>= \y -> return (x+y))) 0
-- Keeping a pair of (predecessor/current) in the state:
let f = (get >>= (\(a,b) -> put (b,a+b))) :: State (Int, Int) ()
runState (f >> f >> f >> f >> f >> f) (0,1)
-- only keeping the predecessor in the state:
let f x = (get >>= (\y -> put x >> return (x+y))) :: State Int Int
runState (return 1 >>= f >>= f >>= f >>= f >>= f >>= f) 0
Also play around with modify, runState, evalState, execState.

Haskell Parser fmap clarification

I have trouble in understanding the following fmap instance.Can someone explain me what fmap do(in this case) and how it can be used? Or write it less obfuscated?
Thanks!
newtype Parser a = P { getParser :: String -> Maybe (a, String) }
instance Functor Parser where
fmap f (P p) = P $ \s -> fmap (applyToFirst f) $ p s
{-|
Applies a function to the first component of a pair.
-}
applyToFirst :: (a -> b) -> (a, c) -> (b, c)
applyToFirst f (x, y) = (f x, y)
What does it do?
It transforms a parser X into parser Y, where Y does the following: runs parser X and applies function f to first element of parsing result pair.
How to use it?
p1 :: Parser String
p1 = P (\s -> Just ("foo", "bar"))
p2 :: Parser String
p2 = fmap (\s -> s ++ s) p1
Now (getParser p2) "whatever" equals Just ("foofoo", "bar").
Could it be less obfuscated?
It is not obfuscated actually. Haskell takes time to get used to.

Converting `do` Notation `addStuff` to `>>=`

Learn You a Haskell presents the addStuff function:
import Control.Monad.Instances
addStuff :: Int -> Int
addStuff = do
a <- (*2) -- binds (*2) to a
b <- (+10) -- binds (+10) to b
return (a+b) -- return has type sig: 'Monad m => a -> m a'
Are the types of a, b, and return (a+b) all Int -> Int? I think so, but I'm not sure how bind-ing plays a role.
I tried to implement it using >>=, but I'm not sure how to complete it (hence ...).
addStuff' :: Int -> Int
addStuff' = (*2) >>= (+10) >>= ...
Please give me a hint to complete it, as well as edit my understanding of the do notation version.
As I understand, the ... needs to include a type of Int -> Int. In the do version, I could use a and b, but I'm not sure how to add them with the >>= version.
When working with the reader monad (a.k.a. the function monad), you have the type a -> b, which can be rewritten as (->) a b. The actual monad instance here is
instance Monad ((->) r) where
return x = const x
f >>= g = \r -> g (f r) r
Notice that during >>=, the type is
(>>=) :: ((->) r a) -> (a -> ((->) r b)) -> ((->) r b)
Which can be rewritten as
(>>=) :: (r -> a) -> (a -> (r -> b)) -> (r -> b)
Or even
(>>=) :: (r -> a) -> (a -> r -> b) -> (r -> b)
So as you can see, what >>= does is take a single input, apply that to f, and then apply that result to g to produce a new function r -> b. So for your example, you could use:
addStuff' :: Int -> Int
addStuff' = (*2) >>= (+)
And so addStuff' 10 == 30, since it performs the computation (10 * 2) + (10). Note how 10 is fed both to (*2) and (+), and the result of (10*2) is fed to (+) as well. It might make things a little more clear to see it as
test :: Int -> (Int, Int, Int)
test = do
x <- (*2)
y <- (*3)
z <- (*5)
return (x, y, z)
And it's result would be
> test 1
(2, 3, 5)
> test 10
(20, 30, 50)
What this essentially is doing is taking the argument to test "before" it's been applied, feeding it to each of the functions on the right hand side of the <-s, and then combining that result in the return.
So how can you write these without do notation? You could do something like
test :: Int -> (Int, Int, Int)
test =
(\r -> r * 2) >>= (\x ->
(\r -> r * 3) >>= (\y ->
(\r -> r * 5) >>= (\z ->
return (x, y, z))))
Which, admittedly, is not very readable, even with formatting, but the gist is basically that r gets fed to each intermediate function, which produces a result, and a couple nested lambda expressions later you return all three of those results in a tuple.
With a bit of simplification, you could also make each of those nested lambdas into two arguments lambdas:
test =
(\r -> r * 2) >>=
(\x r -> r * 3) >>=
(\y r -> r * 5) >>=
(\z r -> const (x, y, z) r)
I've also replaced the last \z -> return (x, y, z) with its equivalent \z -> const (x, y, z) => \z r -> const (x, y, z) r, just so they all have the same form.
As a rough rule if you want to manually desugar do-notation, first erase the do at the top and flip the bind arrow (<-) on the left-hand-side to a (>>=) on the right-hand-side with the variable on the left as a lambda variable on the right. So:
addStuff :: Int -> Int
addStuff = do
a <- (*2)
... rest ...
Becomes:
addStuff :: Int -> Int
addStuff =
(*2) >>= (\a ->
... rest ...
)
This is recursive, so the next term in the do-notation then becomes nested in the lambda of the desugared term above it, all the way down to the last expression which is just the body of the nested lambda expression.
The desugaring is quite mechanical, it's defined by the following rewrites, where ; denotes a newline.
do { a <- f ; m } ≡ f >>= \a -> do { m }
do { f ; m } ≡ f >> do { m }
do { m } ≡ m
Both a and b are of type Int while return (a+b) has type Int -> Int which is the last term in the do-notation so it has to be identical to the toplevel signature. Using -XScopedTypeVariables we can manually annotate the subterms:
{-# LANGUAGE ScopedTypeVariables #-}
import Control.Monad.Instances
addStuff :: Int -> Int
addStuff = do
(a :: Int) <- (*2)
(b :: Int) <- (+10)
(return (a+b)) :: Int -> Int
Thanks to bheklilr.
I wrote my own code.
addStuff :: Int -> Int
addStuff = (\r -> r * 2) >>= (\x ->
(\r -> r + 10) >>= (\y ->
return (x + y)))

Resources