RE: MonadZero (concluded)

1998-11-09 Thread Hans Aberg

At 01:58 -0800 1998/11/09, Simon Peyton-Jones wrote:
Following many protests, the right thing to do seems
to be to move MonadPlus to the Monad library.  Specifically:

   class Monad m = MonadPlus m where
 mzero :: m a
 mplus :: m a - m a - m a

  It seems me that the MonadPlus is just a monad whose algebras are
monoids. So perhaps it should be renamed to reflect that fact.

  Hans Aberg
  * Email: Hans Aberg mailto:[EMAIL PROTECTED]
  * Home Page: http://www.matematik.su.se/~haberg/
  * AMS member listing: http://www.ams.org/cml/







RE: MonadZero (concluded)

1998-11-09 Thread Simon Peyton-Jones


Following many protests, the right thing to do seems
to be to move MonadPlus to the Monad library.  Specifically:

class Monad m = MonadPlus m where
  mzero :: m a
  mplus :: m a - m a - m a

filterM :: MonadZero m = (a - m Bool) - [a] - m [a]
guard   :: MonadZero m = Bool - m ()
mfilter :: MonadZero m = (a - Bool) - m a - m a
concatM :: MonadPlus m = [m a] - m a


Alex, you'll have to use `mplus` instead of (++); or you 
can define a new operator (+++) to mean `mplus`; or you can
hide the list (++) and redefine it to be `mplus`.

I guess that 95% of the mailing list is tired of MonadZero.
If anyone has further thoughts, pls send them to me only
(and, of course, any other individuals you like).

Simon





Re: MonadZero (concluded)

1998-11-07 Thread Erik Meijer

Hi Alex,

Ok, then I am officially complaining about the elimination of ++ and
MonadPlus.  It is a much more radical change than changing default
default and it will break a lot of MY code at very least.

The existing implementation in hugs allows you to write extremely concise
and clean code.  If I want to replace Maybe in my code with a list
implementation then I can do that.  You are taking that away!!

Why are you specializing ++ to lists?  Can you at leat leave ++ as a
function in a class like:

 class Concat a where
  (++)::a-a-a

Or as per my prior mail, define a List class in which I can override ++.

Either way, please please please don't specialize ++ to lists.  It is a
radical and unwarranted change.

I completely agree with you, but most people thought that it is confusing to
overload "list" functions like (++) and (map) to arbitrary monads. Hopefully
you are not relying on monad-comprehensions, because they have been
unoverloaded as well. You don't have to be desparate though. It is easy to
translate from comprehension- to do-notation.

The do-notation is still there for arbitrary monads, and is now even simpler
because (zero) has been moved from MonadZero to Monad. This is really the
only thing that is hardwired in the language and that you cannot change
yourself. From this point you design your own idealized prelude on top of
what is given by hiding, renaming and adding classes and functions. For
example, for the Concat class you want things would look like:

module Alexander'sPrelude where

import Prelude hiding ((++))
import qualified Prelude

class C a where{ (++) :: a - a - a }

instance C ([a]) where { (++) = (Prelude.++) }

-- In non-Hugs Haskell you would use
-- newtype L a = L ([a] - [a])
-- but then I don't like to wrap and unwrap
-- all those silly constructors.

type L a = ([a] - [a]) in ccL, toL, fromL

ccL :: L a - L a - L a
ccL = (.)

toL :: [a] - L a
toL as = \as' - as ++ as'

fromL :: L a - [a]
fromL as = as []

instance C (L a) where { (++) = ccL }

Do you get the idea? As I said before in an earlier message, an extra level
of indirection keeps the doctor away. The pots (do-notation) and the furnace
(the Haskell core language) must be there and work. There is no disputing
about tastes, so as long as I can spice my own food, I am a happy man.

Erik "Haskell98 burns hotter" Meijer






MonadZero (concluded)

1998-11-06 Thread Simon Peyton-Jones

OK, I think we have enough agreement to decide:

class Monad m where
  return :: m a
  (=)  :: m a - (a - m b) - m b
  ()   :: m a - m b - m b

  fail :: String - m a

  fail s = error s

(I'm still a bit nervous about capturing 'fail' but
there seems to be fairly strong support for doing so.)


class Monad m = MonadPlus m where
  mzero :: m a
  mplus :: m a - m a - m a


IO.fail becomes IO.ioError

Simon





Re: MonadZero (concluded)

1998-11-06 Thread Philip Wadler

class Monad m where
  return :: m a
  (=)  :: m a - (a - m b) - m b
  ()   :: m a - m b - m b

  fail :: String - m a
  fail s = error s

IO.fail becomes IO.ioError

Looks good.

class Monad m = MonadPlus m where
  mzero :: m a
  mplus :: m a - m a - m a

Why is this here?  It doesn't need to be in the prelude.  Just
leave it for the user to define (and then the user may pick
better names, like Ringad, zero, and +).  -- P







Re: MonadZero (concluded)

1998-11-06 Thread Ralf Hinze

|   class Monad m = MonadPlus m where
| mzero :: m a
| mplus :: m a - m a - m a
| 
| Why is this here?  It doesn't need to be in the prelude.  Just
| leave it for the user to define (and then the user may pick
| better names, like Ringad, zero, and +).  -- P

Yes, nuke MonadPlus. For Haskell 2 we can put these things in a
wonderful Monad library.

Ralf





Re: MonadZero (concluded)

1998-11-06 Thread Olaf Chitil

Philip Wadler wrote:

 class Monad m = MonadPlus m where
   mzero :: m a
   mplus :: m a - m a - m a
 
 Why is this here?  It doesn't need to be in the prelude.  Just
 leave it for the user to define (and then the user may pick
 better names, like Ringad, zero, and +).  -- P

First, the prelude (or standard libraries) can give instances for [], Maybe and
Error.

More importantly, I believe that monads with plus and zero will appear in many
Haskell programs. Having standard names for them makes programs written by other
people much easier to understand. I'd like to oppose Erik Meijer's statement:

 On the other hand you can easily achieve the
 effect yourself using some hiding and adding a handfull of definitions,
 which is what I will probably end up doing. An extra level of indirection
 can do wonders.

I don't want to read these programs. ;-)

However, I have to admit that I don't like the names mzero and mplus either :-(

Olaf


-- 
OLAF CHITIL, Lehrstuhl fuer Informatik II, RWTH Aachen, 52056 Aachen, Germany
 Tel: (+49/0)241/80-21212; Fax: (+49/0)241/-217
 URL: http://www-i2.informatik.rwth-aachen.de/~chitil/





RE: MonadZero (concluded)

1998-11-06 Thread Simon Peyton-Jones

 | class Monad m = MonadPlus m where
 |   mzero :: m a
 |   mplus :: m a - m a - m a
 | 
 | Why is this here?  It doesn't need to be in the prelude.  Just
 | leave it for the user to define (and then the user may pick
 | better names, like Ringad, zero, and +).  -- P
 
 Yes, nuke MonadPlus. For Haskell 2 we can put these things in a
 wonderful Monad library.

I had thought that too many functions depend on MonadZero/Plus,
but actually, it's the following:

filterM :: MonadZero m = (a - m Bool) - [a] - m [a]
guard   :: MonadZero m = Bool - m ()
mfilter :: MonadZero m = (a - Bool) - m a - m a
concatM :: MonadPlus m = [m a] - m a

These would all vanish, along with MonadZero/Plus.
The Monad library itself doesn't mention MonadZero/Plus, as it happens.

Phil's proposal:
delete class MonadZero, MonadPlus
delete filterM, guard, mfilter, concatM

This is ok by me.  Does anyone object?

Simon





RE: MonadZero (concluded)

1998-11-06 Thread S. Alexander Jacobson

Does this mean that code which relies on ++ and do notation with Maybe
will stop working?

-Alex-

On Fri, 6 Nov 1998, Simon Peyton-Jones wrote:

  |   class Monad m = MonadPlus m where
  | mzero :: m a
  | mplus :: m a - m a - m a
  | 
  | Why is this here?  It doesn't need to be in the prelude.  Just
  | leave it for the user to define (and then the user may pick
  | better names, like Ringad, zero, and +).  -- P
  
  Yes, nuke MonadPlus. For Haskell 2 we can put these things in a
  wonderful Monad library.
 
 I had thought that too many functions depend on MonadZero/Plus,
 but actually, it's the following:
 
 filterM :: MonadZero m = (a - m Bool) - [a] - m [a]
 guard   :: MonadZero m = Bool - m ()
 mfilter :: MonadZero m = (a - Bool) - m a - m a
 concatM :: MonadPlus m = [m a] - m a
 
 These would all vanish, along with MonadZero/Plus.
 The Monad library itself doesn't mention MonadZero/Plus, as it happens.
 
 Phil's proposal:
   delete class MonadZero, MonadPlus
   delete filterM, guard, mfilter, concatM
 
 This is ok by me.  Does anyone object?
 
 Simon
 

___
S. Alexander Jacobson   i2x Media  
1-212-697-0184 voice1-212-697-1427 fax






Re: MonadZero (concluded)

1998-11-06 Thread Meurig Sage

Simon Peyton-Jones wrote:

 Phil's proposal:
 delete class MonadZero, MonadPlus
 delete filterM, guard, mfilter, concatM

 This is ok by me.  Does anyone object?

 Simon

If you're going to do this, are you going to change the Maybe library so
that it has something equivalent to mplus eg
plusMb :: Maybe a - Maybe a - Maybe a

I use this sort of thing a lot. I think I'd prefer MonadPlus to stay
though. Keep it in the Monad library?

Meurig
--
Meurig Sage
Dept of Computing Science
University of Glasgow
http://www.dcs.gla.ac.uk/~meurig
mailto:[EMAIL PROTECTED]







RE: MonadZero (concluded)

1998-11-06 Thread Ralf Hinze

| Does this mean that code which relies on ++ and do notation with Maybe
| will stop working?

++ is specialized to lists, I'm afraid.

Ralf





Re: MonadZero (concluded)

1998-11-06 Thread Lennart Augustsson


 This is ok by me.  Does anyone object?
I don't understand why MonadZero/MonadPlus should go away.
Isn't the idea that when in doubt Haskell 98 should do
what Haskell 1.4 did?  What's the compelling reason for
removing these classes?  I've used several of the functions
that would go away.  It wouldn't be a problem to move these
into my program, but it would be annoying.
If we don't want to have them in the Prelude, maybe we
can move them to a library?  That would only incur minimal
changes in existing programs.

-- Lennart







RE: MonadZero (concluded)

1998-11-06 Thread Christian Sievers

  Yes, nuke MonadPlus. For Haskell 2 we can put these things in a
  wonderful Monad library.
 
 I had thought that too many functions depend on MonadZero/Plus,
 but actually, it's the following:
 
 filterM :: MonadZero m = (a - m Bool) - [a] - m [a]
 guard   :: MonadZero m = Bool - m ()
 mfilter :: MonadZero m = (a - Bool) - m a - m a
 concatM :: MonadPlus m = [m a] - m a
 
 These would all vanish, along with MonadZero/Plus.
 The Monad library itself doesn't mention MonadZero/Plus, as it happens.
 
 Phil's proposal:
   delete class MonadZero, MonadPlus
   delete filterM, guard, mfilter, concatM
 
 This is ok by me.  Does anyone object?

In fact I don't know these functions, but when they were in the
Prelude can they be less important than those in the Monad
library? Why don't we move the classes and functions into a wonderful
Monad library already now for Haskell 98?

And, BTW, the library report defines types for zeroOrMore and
oneOrMore, which both are  (MonadPlus m) = m a - m [a],
but doesn't mention them later.


Christian Sievers





Re: MonadZero (concluded)

1998-11-06 Thread Erik Meijer


Phil's proposal:
 delete class MonadZero, MonadPlus
 delete filterM, guard, mfilter, concatM

This is ok by me.  Does anyone object?

No, not at all. The prelude should be as small as possible. 

Erik






RE: MonadZero (concluded?)

1998-11-05 Thread Simon Peyton-Jones

 There is no need to have both `mzero' and `mfail' in every monad.
 Just have `mfail'.  Leave `zero' and `plus' to MonadPlus.  This should
 make Eric partially happy.  It also means one can simply write
 
   instance Monad [] where
  ...return, =,  as before...
  mfail s = []

Good idea!  So your suggestion is:

class Monad m where
   ...return, =,  as before...

   mfail :: String - m a

class MonadPlus m where
   mplus :: m a - m a - m a
   mzero :: m a

I certainly don't object to that, and it has the merit you mention,
namely that people who don't want zero or plus don't need to fuss with
it.  Should it still be called MonadPlus? (yes, say I... it's a
Monad plus some extra stuff :)

A third alternative (which is more or less what Mark suggested)
is to retain MonadZero also, just as now.  
Monad( return, =, , mfail )
MonadZero( mzero )
MonadPlus( mplus )

That is a smaller change from the present situation, but it's
not clear that the extra monads are worth the candle.

OK, so 

Option 1:   Monad( .., mfail, mzero ), MonadPlus( mplus )
Option 2:   Monad( .., mfail), MonadPlus( mzero, mplus )
Option 3:   Monad( .., mfail), MonadPlus( mplus ), MonadZero( mzero )

I think I like (2) best, but I could live with any of them.
Votes to me (don't copy the list unless you have something else
to say than a vote)

 The names `mzero' and `mfail' are horrible.  I like Ralph's suggestion
 to change `fail' to `raise' in the IO monad, and use `fail' for
 `mfail'.  If that doesn't work, try something else, but please
 pick names that have a simple meaning in English (as with `return')
 not monsters like `mzero' and `mfail'.  -- P

I don't like grabbing too many very generic names like zero, plus, fail
from the user (this is all in the Prelude, remember).  I don't want
to grab 'raise' because we're going to want it for exceptions in Haskell
2.  I havn't been able to think of anything better than these monsters.

Simon





Re: MonadZero (concluded?)

1998-11-05 Thread Lennart Augustsson


 Option 1: Monad( .., mfail, mzero ), MonadPlus( mplus )
 Option 2:   Monad( .., mfail), MonadPlus( mzero, mplus )
 Option 3:   Monad( .., mfail), MonadPlus( mplus ), MonadZero( mzero )
I prefer 3 (with 2 as a close second) since it is most like status quo.

  -- Lennart





RE: MonadZero (concluded?)

1998-11-05 Thread Jon . Fairbairn

On  5 Nov, Simon Peyton-Jones wrote:
  I don't like grabbing too many very generic names like zero, plus, fail
  from the user (this is all in the Prelude, remember).  I don't want
  to grab 'raise' because we're going to want it for exceptions in Haskell
  2.  I havn't been able to think of anything better than these monsters.

um, monadZero, monadFail?  People who can't type can always add their
own renamings.

-- 
Jon Fairbairn [EMAIL PROTECTED]







RE: MonadZero (concluded?)

1998-11-05 Thread Koen Claessen

Simon Peyton-Jones wrote about Phil Wadler's idea:

 | Good idea!  So your suggestion is:
 | 
 |  class Monad m where
 | ...return, =,  as before...
 | 
 | mfail :: String - m a
 | 
 |  class MonadPlus m where
 | mplus :: m a - m a - m a
 | mzero :: m a

I hope you mean:

  class Monad m = MonadPlus m where
mplus :: m a - m a - m a
mzero :: m a

mzero = mfail "mzero" -- maybe?

Regards,
Koen.

--
Koen Claessen,
[EMAIL PROTECTED],
http://www.cs.chalmers.se/~koen,
Chalmers University of Technology.






RE: MonadZero (concluded?)

1998-11-05 Thread Frank A. Christoph

 The names `mzero' and `mfail' are horrible.  I like Ralph's suggestion
 to change `fail' to `raise' in the IO monad, and use `fail' for
 `mfail'.  If that doesn't work, try something else, but please
 pick names that have a simple meaning in English (as with `return')
 not monsters like `mzero' and `mfail'.  -- P

I don't like grabbing too many very generic names like zero, plus, fail
from the user (this is all in the Prelude, remember).  I don't want
to grab 'raise' because we're going to want it for exceptions in Haskell
2.  I havn't been able to think of anything better than these monsters.

"throw" is another possibility.  Of course, someone might want to use this identifier 
in a continuation monad.

--FC







Re: MonadZero (concluded?)

1998-11-04 Thread Philip Wadler

There is no need to have both `mzero' and `mfail' in every monad.
Just have `mfail'.  Leave `zero' and `plus' to MonadPlus.  This should
make Eric partially happy.  It also means one can simply write

instance Monad [] where
   ...return, =,  as before...
   mfail s = []

rather than

instance Monad [] where
   ...return, =,  as before...
   mfail s = mzero
   mzero = []

The names `mzero' and `mfail' are horrible.  I like Ralph's suggestion
to change `fail' to `raise' in the IO monad, and use `fail' for
`mfail'.  If that doesn't work, try something else, but please
pick names that have a simple meaning in English (as with `return')
not monsters like `mzero' and `mfail'.  -- P