[Haskell-cafe] List Monads and non-determinism

Eric Rasmussen ericrasmussen at gmail.com
Sun Jul 21 00:30:11 CEST 2013


For the sake of approaching this in yet another way, it can also be helpful
to substitute the definitions of bind and return in your expression. If we
start with the definitions:

instance Monad [] where
  xs >>= f = concat (map f xs)
  return x = [x]

Then we can make the following transformations:

  [1,2] >>= \n -> [3,4] >>= \m -> return (n,m)

  [1,2] >>= \n -> [3,4] >>= \m -> [(n, m)]

  [1,2] >>= \n -> concat (map (\m -> [(n, m)]) [3,4])

  concat (map (\n -> concat (map (\m -> [(n, m)]) [3,4])) [1,2])

Or perhaps more simply:

  concatMap (\n -> concatMap (\m -> [(n, m)]) [3,4]) [1,2]

All of which are valid expressions and produce the same value.

Depending on your learning style this might not be as helpful as the other
approaches, but it does take a lot of the mystery out of >>= and return.






On Sat, Jul 20, 2013 at 1:08 AM, Alberto G. Corona <agocorona at gmail.com>wrote:

> Matt
>
> It is not return, but the bind the one that does the miracle of
> multiplication.
> By its definition for the list monad, it applies the second term once for
> each element are in the first term.
> So return is called many times. At the end, bind concat all the small
> lists generated
>
>
> 2013/7/20 Matt Ford <matt at dancingfrog.co.uk>
>
>> Hi All,
>>
>> I thought I'd have a go at destructing
>>
>> [1,2] >>= \n -> [3,4] >>= \m -> return (n,m)
>>
>> which results in [(1,3)(1,4),(2,3),(2,4)]
>>
>> I started by putting brackets in
>>
>> ([1,2] >>= \n -> [3,4]) >>= \m -> return (n,m)
>>
>> This immediately fails when evaluated: I expect it's something to do
>> with the n value now not being seen by the final return.
>>
>> It seems to me that the return function is doing something more than
>> it's definition (return x = [x]).
>>
>> If ignore the error introduced by the brackets I have and continue to
>> simplify I get.
>>
>> [3,4,3,4] >>= \m -> return (n,m)
>>
>> Now this obviously won't work as there is no 'n' value.  So what's
>> happening here? Return seems to be doing way more work than lifting the
>> result to a list, how does Haskell know to do this?  Why's it not in the
>> function definition?  Are lists somehow a special case?
>>
>> Any pointers appreciated.
>>
>> Cheers,
>>
>> --
>> Matt
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
>
> --
> Alberto.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130720/2ce2827d/attachment.htm>


More information about the Haskell-Cafe mailing list