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.  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: Tue, 21 Aug 2018 01:04:01 +0100
From: Olumide <50...@web.de>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: [Haskell-beginners] Need better explanation of the
        'flipThree'     example in LYAH
Message-ID: <83c66b35-f934-4a09-4274-24585cb0d...@web.de>
Content-Type: text/plain; charset=utf-8; format=flowed

Dear List,

I'm trying to understand the following example from LYAH

     import Data.List (all)

     flipThree :: Prob Bool
     flipThree = do
         a <- coin
         b <- coin
         c <- loadedCoin
         return (all (==Tails) [a,b,c])

Where
     import Data.Ratio
     newtype Prob a = Prob { getProb :: [(a,Rational)] } deriving Show

and

     data Coin = Heads | Tails deriving (Show, Eq)

     coin :: Prob Coin
     coin = Prob [(Heads,1%2),(Tails,1%2)]

     loadedCoin :: Prob Coin
     loadedCoin = Prob [(Heads,1%10),(Tails,9%10)]

The result:

     ghci> getProb flipThree
     [(False,1 % 40),(False,9 % 40),(False,1 % 40),(False,9 % 40),
      (False,1 % 40),(False,9 % 40),(False,1 % 40),(True,9 % 40)]

See http://learnyouahaskell.com/for-a-few-monads-more#making-monads.

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].

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.

Regards,

- Olumide



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

Message: 2
Date: Tue, 21 Aug 2018 03:00:57 +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: <20180821010057.cyu6pg6mdb5fq...@x60s.casa>
Content-Type: text/plain; charset=us-ascii

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!


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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 122, Issue 11
******************************************

Reply via email to