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. Re:  Need better explanation of the 'flipThree'   example in
      LYAH (Olumide)
   2. Re:  Need better explanation of the 'flipThree'   example in
      LYAH (Francesco Ariis)


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

Message: 1
Date: Mon, 17 Sep 2018 00:16:53 +0100
From: Olumide <50...@web.de>
To: beginners@haskell.org, Francesco Ariis <fa...@ariis.it>
Subject: Re: [Haskell-beginners] Need better explanation of the
        'flipThree'     example in LYAH
Message-ID: <c8d31d36-a46f-c085-4d22-34526aa35...@web.de>
Content-Type: text/plain; charset=utf-8; format=flowed

Hi Francesco,

Thanks as always for your reply. (I note that you've replied many of my 
questions.)

I have not replied because I've been thinking very hard about this 
problem and in particular about the way the do notation is desugared in 
this case and something doesn't sit right with me. (Obviously there's 
something I've failed to understand.)

Take for example

do
     a <- coin
     b <- coin
     return ([a,b])

This would desugar into

do a <- coin
     do b <- coin
         return [a,b]

and ultimately into

coin >>= ( \a ->
coin >>= ( \b ->
return [a,b] ))

Noting that m >>= f = flatten (fmap f m) , and recursively applying 
expanding >>= I get

flatten( fmap (\a -> coin >>= ( \b -> return [a,b] ) ) coin )

and

flatten( fmap (\a -> ( flatten( fmap ( \b -> return [a,b] ) coin ) ) coin )

Is this how to proceed and how am I to simplify this expression?

Regards,

- Olumide




On 21/08/18 02:00, Francesco Ariis wrote:
> Hello Olumide,
> 
> On Tue, Aug 21, 2018 at 01:04:01AM +0100, Olumide wrote:
>> My understanding of what's going on here is sketchy at best. One of several
>> explanations that I am considering is that all combination of a, b and c are
>> evaluated in (==Tails) [a,b,c] but I cannot explain how the all function
>> creates 'fuses' the list [f a, f b, f c]. I know that all f xs = and . map f
>> xs (the definition on hackage is a lot more complicated) but, again, I
>> cannot explain how the and function 'fuses' the list [f a, f b, f c].
> 
> Let's copy the relevant monad instance:
> 
>      instance Monad Prob where
>          return x = Prob [(x,1%1)]
>          m >>= f = flatten (fmap f m)
> 
> and desugar `flipThree:
> 
>      flipThree = coin       >>= \a ->
>                  coin       >>= \b ->
>                  loadedCoin >>= \c ->
>                  return (all (==Tails) [a,b,c])
> 
> 
> Now it should be clearer: `coin >>= \a -> ...something...` takes `coin`
> (Prob [(Heads,1%2),(Tails,1%2)]), applies a function (\a -> ...) to all
> of its elements, flattens (probability wise) the result.
> So approximately we have:
> 
>      1. some list ([a, b])
>      2. nested lists after applying `\a -> ...` [[a1, a2], [b1, b2]]
>      3. some more flattened list [a1, a2, b1, b2]
> 
> `\a -> ...` itself contains `\b ->` which cointains `\c ->`, those are
> nested rounds of the same (>>=) trick we saw above.
> At each time the intermediate result is bound to a variable (\a, \b
> and \c), so for each triplet we can use `all`.
> 
>> If I'm on the right track I realize that I'm going to have to study the list
>> the between list comprehensions and the do-notation in order how all the
>> return function create one Prob.
> 
> Indeed I recall working the example on paper the first time I read it:
> once you do it, it should stick!
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> 


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

Message: 2
Date: Mon, 17 Sep 2018 02:09:18 +0200
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Need better explanation of the
        'flipThree'     example in LYAH
Message-ID: <20180917000917.3ymmmfztomlc4...@x60s.casa>
Content-Type: text/plain; charset=us-ascii

Hello Olumide,

On Mon, Sep 17, 2018 at 12:15:58AM +0100, Sola Aina wrote:
> flatten( fmap (\a -> ( flatten( fmap ( \b -> return [a,b] ) coin ) ) coin )
> 
> Is this how to proceed and how am I to simplify this expression?

I get a slightly different final expression:

    flatten (fmap (\a -> flatten (fmap (\b -> return [a,b]) coin)) coin)
    -- notice the lack of `(` before the second `flatten`

This could be rewritten as:

    flatMap (\a -> flatMap (\b -> return [a,b]) coin) coin

    -- flatMap :: (a1 -> Prob a2) -> Prob a1 -> Prob a2
    -- flatMap f x = flatten (fmap f x)

which is a bit easier on the eyes. This expression cannot be simplified
any further if we don't bring to the table the definition of `coin`!


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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 123, Issue 7
*****************************************

Reply via email to