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

2011-05-31 Thread Lyndon Maydwell
Heh. Looks like there will be about five class constraints, but it
will still be more general.

There must be some higher level abstraction that is less ugly.

On Tue, May 31, 2011 at 3:45 PM, Yves Parès  wrote:
> Maybe you are looking for a more generic way to concatenate it:
> There is fold :: (Foldable t, Monoid m) => t m -> m in Data.Foldable, but it
> would add another Foldable constraint.
>
> You search a function like:
> concatMPlus :: (MonadPlus m, Monoid a) => m a -> a
> but this cannot exist ;) ("m a -> m a" would, but not "m a -> a")
>
>
> 2011/5/31 Lyndon Maydwell 
>>
>> I think this is because mconcat expects a list.
>>
>> On Tue, May 31, 2011 at 3:31 PM, John Ky  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  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@haskell.org
>> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >
>> >
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-31 Thread Yves Parès
Maybe you are looking for a more generic way to concatenate it:
There is 
fold::
(Foldable t, Monoid m) => t
m -> 
min
Data.Foldable, but it would add another Foldable constraint.

You search a function like:
concatMPlus :: (MonadPlus m, Monoid a) => m a -> a
but this cannot exist ;) ("m a -> m a" would, but not "m a -> a")


2011/5/31 Lyndon Maydwell 

> I think this is because mconcat expects a list.
>
> On Tue, May 31, 2011 at 3:31 PM, John Ky  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  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@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> >
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-31 Thread Lyndon Maydwell
I think this is because mconcat expects a list.

On Tue, May 31, 2011 at 3:31 PM, John Ky  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  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@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-31 Thread John Ky
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  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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-30 Thread Malcolm Wallace

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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-30 Thread Canhua
sorry, `m a` as an instance of Monoid, not `m'

On Tue, May 31, 2011 at 9:30 AM, Canhua  wrote:
> I think you should declare `m' as an instance of Monoid,
> rather than as instnaces of Monad and MonadPlus
>
> On Tue, May 31, 2011 at 8:33 AM, John Ky  wrote:
>> Hi Brandon,
>> Thanks for your suggestion.  I'm a little stuck as adding Monad and
>> MonadPlus in my instance declaration doesn't seem sufficient.  I know
>> mconcat comes from Monoid, but I don't know how to put that in.
>> data Stream m a
>> = Chunks (m a)
>> | EOF
>> deriving (Show, Eq)
>> instance (Monad m, MonadPlus m) => 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
>> Iteratee.hs:28:25:
>>     No instance for (Monoid (m a))
>>       arising from a use of `mempty'
>>     Possible fix: add an instance declaration for (Monoid (m a))
>>     In the first argument of `Chunks', namely `mempty'
>>     In the expression: Chunks mempty
>>     In an equation for `mempty': mempty = Chunks mempty
>> Iteratee.hs:29:54:
>>     No instance for (Monoid (m a))
>>       arising from a use of `mappend'
>>     Possible fix: add an instance declaration for (Monoid (m a))
>>     In the first argument of `Chunks', namely `(xs `mappend` ys)'
>>     In the expression: Chunks (xs `mappend` ys)
>>     In an equation for `mappend':
>>         mappend (Chunks xs) (Chunks ys) = Chunks (xs `mappend` ys)
>> Iteratee.hs:34:43:
>>     Could not deduce (m ~ [])
>>     from the context (Monad m, MonadPlus m)
>>       bound by the instance declaration at Iteratee.hs:32:10-51
>>       `m' is a rigid type variable bound by
>>           the instance declaration at Iteratee.hs:32: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)
>> Failed, modules loaded: none.
>> Cheers,
>> -John
>> On 31 May 2011 00:38, Brandon Moore  wrote:
>>>
>>> >From: John Ky 
>>> >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@haskell.org
>>> >http://www.haskell.org/mailman/listinfo/haskell-cafe
>>> >
>>> >
>>> >
>>
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-30 Thread John Ky
Hi Brandon,

Thanks for your suggestion.  I'm a little stuck as adding Monad and
MonadPlus in my instance declaration doesn't seem sufficient.  I know
mconcat comes from Monoid, but I don't know how to put that in.

data Stream m a
= Chunks (m a)
| EOF
deriving (Show, Eq)

instance (Monad m, MonadPlus m) => 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

Iteratee.hs:28:25:
No instance for (Monoid (m a))
  arising from a use of `mempty'
Possible fix: add an instance declaration for (Monoid (m a))
In the first argument of `Chunks', namely `mempty'
In the expression: Chunks mempty
In an equation for `mempty': mempty = Chunks mempty

Iteratee.hs:29:54:
No instance for (Monoid (m a))
  arising from a use of `mappend'
Possible fix: add an instance declaration for (Monoid (m a))
In the first argument of `Chunks', namely `(xs `mappend` ys)'
In the expression: Chunks (xs `mappend` ys)
In an equation for `mappend':
mappend (Chunks xs) (Chunks ys) = Chunks (xs `mappend` ys)

Iteratee.hs:34:43:
Could not deduce (m ~ [])
from the context (Monad m, MonadPlus m)
  bound by the instance declaration at Iteratee.hs:32:10-51
  `m' is a rigid type variable bound by
  the instance declaration at Iteratee.hs:32: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)
Failed, modules loaded: none.

Cheers,

-John

On 31 May 2011 00:38, Brandon Moore  wrote:

> >From: John Ky 
> >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@haskell.org
> >http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> >
> >
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-30 Thread Lyndon Maydwell
I just tried to use the generic form with (Maybe a) and 'mconcat'
prevented this from working, so that needs to be considered too.

On Mon, May 30, 2011 at 10:53 PM, Casey McCann  wrote:
> On Mon, May 30, 2011 at 9:01 AM, John Ky  wrote:
>> 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:
>
> I don't care for the inconsistency in this example, using both mempty
> and (++). Your version is at least consistent, but I'd actually prefer
> to use mappend instead of (++) here, because it makes it clear that
> this isn't actually defining a "new" Monoid instance, just translating
> an existing instance for the constructor parameter to work for the
> surrounding data type.
>
> - C.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-30 Thread Casey McCann
On Mon, May 30, 2011 at 9:01 AM, John Ky  wrote:
> 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:

I don't care for the inconsistency in this example, using both mempty
and (++). Your version is at least consistent, but I'd actually prefer
to use mappend instead of (++) here, because it makes it clear that
this isn't actually defining a "new" Monoid instance, just translating
an existing instance for the constructor parameter to work for the
surrounding data type.

- C.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-30 Thread Brandon Moore
>From: John Ky 
>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@haskell.org
>http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-30 Thread Lyndon Maydwell
Because they are more general functions that work on all monads rather
than just lists.

This allows Stream to be defined more flexibly.

On Mon, May 30, 2011 at 9:01 PM, John Ky  wrote:
> 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:
>
> 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@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-30 Thread John Ky
Hi all,

I'm trying to learn about enumerators by reading this
paperand
came across some code on page 2 that I found hard to digest, but I
think
I finally got it:

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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe