Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Join'ing a State Monad, example from LYH (Olumide)
   2. Re:  Join'ing a State Monad, example from LYH (Francesco Ariis)


----------------------------------------------------------------------

Message: 1
Date: Sat, 10 Feb 2018 14:48:07 +0000
From: Olumide <50...@web.de>
To: beginners@haskell.org
Subject: [Haskell-beginners] Join'ing a State Monad, example from LYH
Message-ID: <edf89a88-b331-b42d-572b-e6b128d67...@web.de>
Content-Type: text/plain; charset=utf-8; format=flowed

Dear List,

I've been stumped for a few months on the following example, from 
chapter 13 of LYH
http://learnyouahaskell.com/for-a-few-monads-more#useful-monadic-functions

runState (join (State $ \s -> (push 10,1:2:s))) [0,0,0]

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

In contrast, I find the following definition(?) on Haskell Wikibooks
https://en.wikibooks.org/wiki/Haskell/Category_theory#Monads

join :: Monad m => m (m a) -> m a
join x = x >>= id

easier to understand, and although I can apply it to the following 
Writer Monad example, in the same section of LYH,

runWriter $ join (Writer (Writer (1,"aaa"),"bbb"))

I cannot apply it to the State Monad example.

Regards,

- Olumide


------------------------------

Message: 2
Date: Sat, 10 Feb 2018 16:25:40 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Join'ing a State Monad, example from
        LYH
Message-ID: <20180210152540.llwsh53dgobkw...@x60s.casa>
Content-Type: text/plain; charset=us-ascii

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


------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 116, Issue 1
*****************************************

Reply via email to