[Haskell-beginners] Join'ing a State Monad, example from LYH
Olumide
50295 at web.de
Thu May 10 00:24:31 UTC 2018
Francesco,
Your explantion makes sense but in a very general way that still left me
trying, and failing, explain why the result of
runState (join (State $ \s -> (push 10,1:2:s))) [0,0,0]
is ((),[10,1,2,0,0,0]).
After so many months of thinking I think I now do. Here's my reasoning,
please correct me if I am wrong. I'm sure my explanation is far from
precise even if the jist of it is correct, so I'd appreciate corrections
about that too.
As you said join mm = mm >>= \m -> m.
\m -> m looks like the identify function, so that join x = x >>= id,
(from Haskell Wikibooks).
Considering the definition of the State monad bind
(State h) >>= f = State $ \s -> let (a, newState) = h s
(State g) = f a
in g newState
where h is \s -> (push 10,1:2:s), h s = (push 10,1:2:s)
where a = push 10 and newState = 1:2:s
Also f = id, so that f a = push 10 = State $ \xs -> ((),10:xs),
where g = \xs -> ((),10:xs)
Finally, g newState = ((),10:1:2:s)
So that, join (State $ \s -> (push 10,1:2:s) = state \s -> ((),10:1:2:s)
Finally runState( state \s -> ((),10:1:2:s) ) [0,0,0]
= (\s -> ((),10:1:2:s) ) [0,0,0] = ((),10,1,2,0,0,0)
Regards,
- Olumide
On 10/02/18 15:25, Francesco Ariis wrote:
> On Sat, Feb 10, 2018 at 02:48:07PM +0000, Olumide wrote:
>> I find the following implementation of join in the text is hard to
>> understand or apply
>>
>> join :: (Monad m) => m (m a) -> m a
>> join mm = do
>> m <- mm
>> m
>
> Hello Olumide,
>
> remember that:
>
> join :: (Monad m) => m (m a) -> m a
> join mm = do m <- mm
> m
>
> is the same as:
>
> join :: (Monad m) => m (m a) -> m a
> join mm = mm >>= \m ->
> m
>
> In general remember that when you have a "plain" value, the last line
> of a monadic expression is often:
>
> return someSimpleVal
>
> So:
>
> monadicexpr = do x <- [4]
> return x -- can't just write `x`
>
> When you have a monad inside a monad, you can just "peel" the outer
> layer and live happily thereafter:
>
>
> monadicexpr = do x <- [[4]]
> x -- result will be: [4], no need to use return
> -- because [4] (and not 4) is still a
> -- list monad
>
> As for State, remember that State is:
>
> data State s a = State $ s -> (a, s) -- almost
>
> So a function that from a state s, calculates a new state s' and returns
> a value of type `a`.
> When we use the bind operator in a do block, it's like we're extracting
> that value of type `a`
>
> monadicexpr = do x <- someState
> return x -- again we need to wrap this value
> -- before returning it, this state being
> --
> -- \s -> (x, s)
> --
> -- i.e. we do nothing to the parameter state
> -- and place `x` as a result.
> --
>
> Same trick there, if `x` is actually a State-inside-State (e.g. of
> type `State s (State s a)`), there is no need for wrapping anymore.
>
> Does this make sense?
> -F
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
More information about the Beginners
mailing list