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

Lyndon Maydwell maydwell at gmail.com
Tue May 31 09:39:35 CEST 2011


I think this is because mconcat expects a list.

On Tue, May 31, 2011 at 3:31 PM, John Ky <newhoggy at gmail.com> wrote:
> Thanks Malcom.
> I suspected that much, so I added it:
> data Stream m a
> = Chunks (m a)
> | EOF
> deriving (Show, Eq)
> instance (Monad m, MonadPlus m, Monoid (m a)) => Monoid (Stream m a) where
> mempty = Chunks mempty
> mappend (Chunks xs) (Chunks ys) = Chunks (xs `mappend` ys)
> mappend _ _ = EOF
> instance (Monad m, MonadPlus m) => Monad (Stream m) where
> return = Chunks . return
> Chunks xs >>= f = mconcat (fmap f xs)
> EOF >>= _ = EOF
> This gives me the error:
> Iteratee.hs:30:10:
>     Non type-variable argument in the constraint: Monoid (m a)
>     (Use -XFlexibleContexts to permit this)
>     In the context: (Monad m, MonadPlus m, Monoid (m a))
>     While checking the context of an instance declaration
>     In the instance declaration for `Monoid (Stream m a)'
> So I run with the new flag:
> ghci -XFlexibleContexts Iteratee.hs
> Then I get the following error instead:
> Iteratee.hs:37:43:
>     Could not deduce (m ~ [])
>     from the context (Monad m, MonadPlus m)
>       bound by the instance declaration at Iteratee.hs:35:10-51
>       `m' is a rigid type variable bound by
>           the instance declaration at Iteratee.hs:35:17
>     Expected type: [a]
>       Actual type: m a
>     In the second argument of `fmap', namely `xs'
>     In the first argument of `mconcat', namely `(fmap f xs)'
>     In the expression: mconcat (fmap f xs)
> Which is complaining about the line I highlighted above.  So I try:
> data Stream m a
> = Chunks (m a)
> | EOF
> deriving (Show, Eq)
> instance (Monad m, MonadPlus m, Monoid (m a)) => Monoid (Stream m a) where
> mempty = Chunks mempty
> mappend (Chunks xs) (Chunks ys) = Chunks (xs `mappend` ys)
> mappend _ _ = EOF
> instance (Monad m, MonadPlus m, Monoid (m a)) => Monad (Stream m) where
> return = Chunks . return
> Chunks xs >>= f = mconcat (fmap f xs)
> EOF >>= _ = EOF
> But the same trick doesn't work:
> Iteratee.hs:35:10:
>     Variable occurs more often in a constraint than in the instance head
>       in the constraint: Monoid (m a)
>     (Use -XUndecidableInstances to permit this)
>     In the instance declaration for `Monad (Stream m)'
> Is that because I don't use a on the right hand side of =>?
> Cheers,
> -John
> On 31 May 2011 15:54, Malcolm Wallace <malcolm.wallace at me.com> wrote:
>>
>> instance (Monad m, MonadPlus m) => Monoid (Stream m a) where
>>
>> mempty = Chunks mempty
>> mappend (Chunks xs) (Chunks ys) = Chunks (xs `mappend` ys)
>> mappend _ _ = EOF
>>
>> Iteratee.hs:28:25:
>>     No instance for (Monoid (m a))
>>       arising from a use of `mempty'
>>
>> There is a clue in the first part of the error message.  Add the required
>> instance as part of the predicate:
>> instance (Monad m, MonadPlus m, Monoid (m a)) => Monoid (Stream m a) where
>> ...
>
> _______________________________________________
> 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