[Haskell-cafe] What's the advantage of writing Haskell this way?

Brandon Moore brandon_m_moore at yahoo.com
Mon May 30 16:38:07 CEST 2011


>From: John Ky <newhoggy at gmail.com>
>Sent: Monday, May 30, 2011 8:01 AM
>
>Hi all,
>
>I'm trying to learn about enumerators by reading this paper and came across some code on page 2 that I found hard to digest, but I think I finally got it:


Hi John. These programs should behave identically, and I think your version should be preferred.
This first code uses some class methods like mconcat, but it seems to always be used on
the list in Chunks, so it will only ever use the definition for list, which is equivalent to what
you wrote directly in the second code.

The result may not be useful, but to understand this more thoroughly you might
try parametrizating the definition of Stream so the use of more general operators
actually means something. Perhaps

data Stream m a =
  Chunks (m a)
  | EOF

I think you would want Monad and MonadPlus on m.


>import Data.Monoid
>>
>>
>>data Stream a
>>= Chunks [a]
>>| EOF
>>deriving (Show, Eq)
>>
>>
>>instance Monad Stream where
>>return = Chunks . return
>>Chunks xs >>= f = mconcat (fmap f xs)
>>EOF >>= _ = EOF
>>
>>
>>instance Monoid (Stream a) where
>>mempty = Chunks mempty
>>mappend (Chunks xs) (Chunks ys) = Chunks (xs ++ ys)
>>mappend _ _ = EOF
>
>
>I guess, it shows my lack of experience in Haskell, but my question is, why is writing the code this way preferred over say writing it like this:
>
>
>import Data.Monoid
>>
>>
>>data Stream a
>>= Chunks [a]
>>| EOF
>>deriving (Show, Eq)
>>
>>
>>instance Monad Stream where
>>return x = Chunks [x]
>>Chunks xs >>= f = mconcat (fmap f xs)
>>EOF >>= _ = EOF
>>
>>
>>instance Monoid (Stream a) where
>>mempty = Chunks []
>>mappend (Chunks xs) (Chunks ys) = Chunks (xs ++ ys)
>>mappend _ _ = EOF
>
>
>Cheers,
>
>
>-John
>
>
>_______________________________________________
>Haskell-Cafe mailing list
>Haskell-Cafe at haskell.org
>http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
>



More information about the Haskell-Cafe mailing list