MonadZero, MonadPlus

1998-11-11 Thread Klaus Georg Barthelmann

The following is independent of whether MonadPlus is moved to the library
or not. Therefore I dare to raise a new issue that is related to monads ...

As I understand it, class Monad now contains fail and the IO monad is no
longer a subclass of Monad. Wouldn't it be nice, then, to add a predicate
  isZero :: m a -> Bool
(or similar) to MonadPlus, whose purpose is to distinguish the value of
mzero? All datatypes which are instances of MonadPlus already have such
a predicate, or at least it could be implemented easily. To my knowledge,
the IO monad was the only example that did not allow such a predicate.
Since this obstacle is gone, datatype interfaces could be unified a bit
more.

Klaus

--
Klaus Barthelmann, Johannes Gutenberg-Universitat, Institut fur Informatik,
D-55099 Mainz, Germany
[EMAIL PROTECTED]





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 
  * Home Page: 
  * AMS member listing: 







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






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-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 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 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 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

|   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 S. Alexander Jacobson

On Fri, 6 Nov 1998, Ralf Hinze wrote:
> | Does this mean that code which relies on ++ and do notation with Maybe
> | will stop working?
> ++ is specialized to lists, I'm afraid.

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. 

-Alex-

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








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 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 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





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-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

1998-11-05 Thread Christian Sievers

Hi, it seems to be much too late after all the discussion but among
the alternatives was

>   3.  Make tuples special, so that g would be in Monad, but
>   if we had a user-defined single-constructor type instead
>   then it would be in MonadZero

about which was said

> (3) seems dreadful.

I'm not so sure. If we don't call it make them special, but let them
be unlifted products (and hence irrefutable patterns), how would that
sound? Why are they lifted, anyway? If it's only so that we can say
tuples are nothing but syntactic sugar for something one might
otherwise declare as a data definition oneself, I'd be happy to give
that away. And I never liked the lifting of single-constructor types,
so I don't use them. After all, there is still newtype.

I also like (5) [status quo].
I don't feel happy with the proposed changings in the definition of
Monad, but I can't give good (let alone new) reasons for that.


Christian Sievers





Re: MonadZero

1998-11-05 Thread Fergus Henderson

On 04-Nov-1998, Erik Meijer <[EMAIL PROTECTED]> wrote:
> Let me try to sketch a design methodology for introducing type classes
[...]
> It is good style to define non-overloaded versions of class methods outside
> of the class instead of inlining them in the instance declaration. For
> example the usual instance declaration Eq a => Eq [a] is utterly confusion.
> Instead first define eqList :: Eq a => [a] -> [a] -> Bool and then simple
> say instance Eq a => Eq [a] where { (==) = eqList }.

I'm not sure I'd agree with this.  Defining all of those non-overloaded
versions of class methods requires inventing a lot of names;
I find the resulting namespace polution can be a bit ugly.

> It is bad style to have trivial definitions for class methods, in which case
> you are lying to the user.

I don't know what you mean here.  Could you explain this in more detail?

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





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 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 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 Philip Wadler

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

Following Erik's note, I suggest:

  Option 4:  Monad( (>>=), return, mfail)

The user can define MonadZero, MonadPlus, etc. as desired -- we don't
need to specify this in the prelude.  This also means we only need
to come up with a better name for `mfail'.  How about `reject'?

  Option 4':  Monad( (>>=), return, reject)

-- P





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-04 Thread Erik Meijer

Hi fellow debaters,

>I hope you've had fun with all the MonadZero mail.

I surely did.

>My conclusion: we should combine Monad and MonadZero.
>Sorry Erik, but you are now the lone voice in the wilderness.

Don't worry, I am used to that :-)

>Here's a concrete proposal:
>
>That's it!  Comments?

Looks ok to me, only I would write the translation of do as

do{ p <- e; stmts } =
  e >>= \x ->
case x of
  { p -> do{ stmts }
  ; _ -> mfail "."
  }

>Simon

Some remarks about
http://research.microsoft.com/Users/simonpj/Haskell/haskell98-final.html

* I don't understand unfoldr! The proposed definition is

unfoldr :: (a -> Maybe (b,a)) -> a -> (a,[b])
unfoldr f = g where
  g = \a ->
 case f a of
  { Nothing -> (a,[])
  ; Just (b,a') -> let (a'',bs) = g a' in  (a'',b:bs)
  }

But note that in general unfold is used to build *infinite* lists. Pulling
on the fst of the resulting pair therefore leads to disaster in most cases.

ones = unfoldr (\a -> Just (1,a)) 17

Why the extra generality? Why not use the normal unfold from Bird and Wadler
and from Geremy's and Graham's papers from this year's ICFP?

* What will be the fixity and precedence of ($!), the same as ($) I guess.

* Let's leave the default default.

* Let's give type variables in head position the benefit of the doubt. Given
the pre-constructor class restrictions of Haskell, this *feels* like the
right generalization.

* The sentence "Section 5.4.2. Name clashes only cause an error if the
offending name is actually mentioned.now a" ends strangely.

* You probably already know this: "Section ??. Class declarations can
contain intermingled type signatures, fixity declarations, and value
declarations for default class methods. "

I must admit that I had my doubts about the whole Haskell98 adventure, but
in the end I do believe that the language has been refreshed and improved.

Erik

PS

Has anybody read the "anti-patterns" book (is a joke, or is it serious?),
and heard about the name change of NT5 to Windows2000 (very smart way of
creating an extra year of slack). Perhaps Haskell98 is not such a cool name
after all :-)






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








MonadZero

1998-11-04 Thread Colin . Runciman

I'm with the Option 2 Zap MonadZero Today lobby.

I dislike ~ patterns for all sorts of reasons (won't drag up all *that*
again now!) but that the introduction or elimination of a ~ can alter
the *type* of an expression is particularly horrible.

The attempt to introduce notions of guaranteed evaluation in types is
something we have already backed off for Haskell '98 (eg. class Eval).

Haskell '98 does not attempt to distinguish non-empty or infinite lists
in the static type system, despite the extra guarantees this could
give.  Nor does it attempt to distinguish total from partial functions
(eg by pattern coverage) in the static type system, ditto.  So arguably
MonadZero is just a complicating anomaly.

As Eric says, there is a trade-off between the extent of static
guarantees on the one hand and pragmatic simplicity on the other.
I am unashamedly in favour of pragmatic simplicity, particularly when
the type system is already quite complex for widespread use.

Option 2.  Zap!

Colin R






Re: MonadZero

1998-11-04 Thread lex

> The nice thing about Monads+the do-notation is that  it gives you a natural
> hook to catch pattern match failures! We must nurture every chance we have
> to improve staticness of typing. I don't agree with your argument that
> because pattern match failure in function definitions is not catched by the
> type-checker justifies dropping that extra safety for pattern matching in
> the do-notation.

The problem of failing pattern matching can be handled in a different way.
have a look at Elegant 
(http://www.research.philips.com/generalinfo/special/elegant/elegant.html).

Here, constructors are types, more precesiely, they are sub-types.
Thus in 

  List a = Null | Cons a (List a)

List is a type, Null a sub-type of List and Cons a sub-type of List.

The function

  head (Cons a _) = a

is treated by the type checker as a partial function, only defined for
the sub-type Cons and not for the whole type List.
The type checker will issue compile-time warnings and run-time checks for
any caller of head that does not ensure statically that the argument is
of type Cons. These warnings could be errors if you want even more safety.

The type checker is not so smart that it can treat every pattern as a type.
It rounds patterns to the nearest higher super-type. Thus the type of

  foo (Cons a Null) = a

is just Cons a -> a.

But in this case, the type checker will issue a compile time warning that
the type of foo is incomplete. It misses the case (Cons a _). 
Note that it does not enforce the case (Null), it allows foo to be partial, 
but not too partial.

Observe that pattern matching now has become equivalent to run-time 
type-analysis.

Both features (checking on coercions to sub-types and missing patterns)
have proven to be very convient and remove allmost all run-time errors in this
category, unless the programmer has ingnored a static warning.
A counter example is the list-indexing function, which is partial but can
not be proven correct at compile time (maybe with dependant types ...).

Is this something for Haskell-3? :-)

> As Koen said, some of the proposed type weakenings (unoverloading
> list-comprehensions, junking MonadZero) are partly motived by the fact that
> the type checker gives bad error messages. Well, I rather have bad error
> messages from the type checker than good error messages at run-time! Perl,
> Tcl, Visual Basic, Phyton, etc are great languages from this perspective,
> their type checker *never* complains.

Agreed Erik. Solve the problem in the proper way: improve the error messages.

> Strong typing is what distinguishes Haskell from the muck, let's be proud of
> it. I cannot believe that the Dutch are the only prim and proper
> programmers! Or maybe I concentrate too much on type safety to the detriment
> of simplicity and pragmatism. In any case, we must be fully aware of the
> fact that we trade the one for the other.

I think treating constructors as sub-types makes things both more simple and
more safe. But well, I'm Dutch too :-).

Lex





Re: MonadZero

1998-11-04 Thread Mark P Jones

| I don't agree with your argument that
| because pattern match failure in function definitions is not catched by the
| type-checker justifies dropping that extra safety for pattern matching in
| the do-notation.

You've missed my point, the nub of which was that we should get
our compilers to check for exhaustive pattern matches, and to
report errors (or warnings, as Ralf prefers) for non-exhaustive
matches.  This would catch strictly more errors than changes in
the typing rules for do notation.  Haskell doesn't require the
former at the moment, and Hugs doesn't test for it.  Clearly, we
should fix that.  The treatment of do notation should be handled
as a separate issue.

| As Koen said, some of the proposed type weakenings (unoverloading
| list-comprehensions, junking MonadZero) are partly motived by the fact that
| the type checker gives bad error messages.  Well, I rather have bad error
| messages from the type checker than good error messages at run-time!

Yes, and adding a check for non-exhaustive pattern matches also gives
you error messages at compile-time rather than run-time; and it can
detect more of them.  What does your proposal offer that mine lacks?

| Strong typing is what distinguishes Haskell from the muck, let's be
| proud of it.

Be proud of it, but recognize its limitations, and also the other options
that can sometimes do a better job.

All the best,
Mark





Re: MonadZero

1998-11-04 Thread Erik Meijer

John,

>Of course we would all like Haskell to catch as many errors as possible,
and statically. But a chain is only as strong as its weakest link. When
there are already weak links in a chain, it makes no sense to build others
of some hi-tech super strong material. The most efficient design occurs when
all the links are approximately the same strength.
>[...]
>So the question is, with the rest of Haskell as it is, what choice for
>MonadZero most closely matches the rest of the language?
>
>I am more convinced than ever: nuke MonadZero.

I agree with your your premisses, but not with your conclusion. If you take
your reasoning to the extreme (and that's what I like to do :-) the
conclusion is that we only need one class for types of kind *, one for types
of kind * -> *, etc. That is not what we want, I hope.

Let me try to sketch a design methodology for introducing type classes, and
convince you that aside from issues of type safety or the do-notation it is
good to separate Monad and MonadZero. This should also answer Phil's
question wether
there is "anyone out there who values the separation of Monad and MonadZero
for purposes other than `do' notation?".

rule 0: Class introduction

Introduce a class Foo a where { foo :: ...a...} when there are at least two
types X and Y with non-trival and different definitions for fooX :: ...X...
and fooY :: ...Y, and you want to abstract from X and Y when using foo.
The instances for Foo are instance Foo X where { foo = fooX } and Foo Y
where { foo = fooY }.

When there is just a single type Z for which you can define fooY :: ...Y...
there is no need to abstract over it, and fooY can just as well be
identified with foo.

When for all types a the definitions of fooa are the same, we can just
define foo :: ...a... as a polymorphic function.

It is good style to define non-overloaded versions of class methods outside
of the class instead of inlining them in the instance declaration. For
example the usual instance declaration Eq a => Eq [a] is utterly confusion.
Instead first define eqList :: Eq a => [a] -> [a] -> Bool and then simple
say instance Eq a => Eq [a] where { (==) = eqList }.

It is bad style to have trivial definitions for class methods, in which case
you are lying to the user.

Often there are different implementations for fooX and fooY where Y and X
overlap (e.g. X=[Char] and Y = [a]) but where you don't want to make the
less general one abstract (e.g. I dont want to define newtype String =
String [Char]).

rule 1: Subclass introduction

Introduce a sublass Foo a => Bar a where { bar :: ...a... } when rule 1
tells you to introduce Bar for a proper subset of the instances of Foo.

When all instances of Foo are also instances of Bar, you should add bar to
the methods of Foo.

When there are instances of Bar that are not instances of Foo, Bar should be
a seperate class.

According to these rules Monad and MonadZero should be different classes,
and MonadZero and MonadPlus should be merged. Why Monad? Because we have
{bindId, returnId}, {bindReader, returnReader}, {bindMaybe, returnMaybe},
{bindList, returnList}, {bindIO, returnIO}, {bindST, returnST}. Why
MonadZero? Because we don't have non-trivial definitions for {zeroId},
{zeroReader}, and {zeroST}, but we do have {zeroMaybe}, {zeroList}, and
{zeroIO}. Why merge MonadZero and MonadPlus? Because we have {plusMaybe},
{plusList}, and {plusIO}.

According to these rules we should *not* have Show and Eq as subclasses for
Num.

I think that it is good that recursion, undefined and (less so for) seq are
polymorphic and thus that all Haskell functions are implicitely partial.
According to these rules, there should be no Eval class.

According to these rules, much of the rest of the Numeric class hierarchy
can be justified, and I guess that the original designers used a similar
methodology as I gave.

It is disheartening however, that we want to flatten a hierarchy that is
flat and simple, while it is a taboo to talk about simplifying and
collapsing the complex and deep numeric hierarchy. About 80% of the problems
my students have when doing their programming exercises is with these
classes. We are hunting something tiny and neglect something big.

Erik, Haskell Certified Software Engineer, Meijer






RE: MonadZero

1998-11-03 Thread Ralf Hinze

| I agree that this is an error that you would like the system to catch.
| I disagree strongly with the suggestion that this is an error that you
| should expect the *type system* to catch.
| 
| Suppose that the original version of your nuclear reactor driver also
| contained a definition:
| 
|inCaseOfEmergency Open = ...
| 
| When an extra constructor is added to the datatype, you would hope that
| your compiler might report a "non-exhaustive pattern match" error here,
| alerting the programmer to the fact that modifications to this function
| definition might be required.  This isn't a type error, it's a question
| about values within a type, and about whether you manage to cover all 
| the possibilities.
| 
| Likewise, your definition of controlReactor might reasonably be
| expected to generate a "non-exhaustive pattern match" error when
| the second constructor is added.
| 
| You'll be seriously misleading designers of nuclear reactor drivers,
| as well as those for more mundane appliances, if you tell them that
| Haskell's ability to raise a type error in situations like this will
| make the language safer.  For one thing, it only applies to do notation,
| and not to pattern matches in function definitions.  For another, it
| wouldn't do anything to help in situations where a datatype with two
| constructors is modified to add a third.
| 
| So here is good motivation for adding mechanisms to check for exhaustive
| pattern matches, but not for choosing between the alternatives that
| are being considered for do notation.

I fully and strongly agree with Mark's statement except for one minor
point ;-). A compiler should issue a warning (as opposed to an error)
in both cases.

Cheers, Ralf





Re: MonadZero

1998-11-03 Thread Ralf Hinze

| I want to make a different plea: keep the language design consistent!
| Yes, the difference between f, g, h is a wart, but let's have one wart
| repeated, rather than two different warts.

I am not convinced. This argument could be reverted to support
alternative 2. Haskell uses patterns in many different places,
monad expressions among other things. Why should we introduce
concepts (irrefutable, unfailable) only for monad expressions?
Why is
head (a : as)   =  a
legal, but not
do { ... (a : as) <- e ... }
So, to keep the language design consistent, let's adopt 2. The
expression `head []' fails (which means `error "..."' in the Id monad)
and the computation `(a : as) <- e' fails, as well (which means `mfail'
in an arbitrary monad).

A comment on names: I propose to use `fail' for the class method
and to rename IO's fail to `raise' which IMHO is more consistent
(the Report says: the `fail' function _raises_ an exception ...).

Cheers, Ralf







RE: MonadZero

1998-11-03 Thread Mark P Jones

| > b) if you add an extra constructor to a single-constructor type
| >then pattern matches on the original constructor suddenly become
| >failable
| 
| That is great. I'd rather have this as a static error that getting an
| unexpected pattern match failure in my nuclear reactor device driver:
| 
|data Position = Open | Close
|controlReactor = do{ .; Open <- checkValve; ... }
| 
| than have this fail silently using the default definition mfail = 
| undefined.

I agree that this is an error that you would like the system to catch.
I disagree strongly with the suggestion that this is an error that you
should expect the *type system* to catch.

Suppose that the original version of your nuclear reactor driver also
contained a definition:

   inCaseOfEmergency Open = ...

When an extra constructor is added to the datatype, you would hope that
your compiler might report a "non-exhaustive pattern match" error here,
alerting the programmer to the fact that modifications to this function
definition might be required.  This isn't a type error, it's a question
about values within a type, and about whether you manage to cover all 
the possibilities.

Likewise, your definition of controlReactor might reasonably be
expected to generate a "non-exhaustive pattern match" error when
the second constructor is added.

You'll be seriously misleading designers of nuclear reactor drivers,
as well as those for more mundane appliances, if you tell them that
Haskell's ability to raise a type error in situations like this will
make the language safer.  For one thing, it only applies to do notation,
and not to pattern matches in function definitions.  For another, it
wouldn't do anything to help in situations where a datatype with two
constructors is modified to add a third.

So here is good motivation for adding mechanisms to check for exhaustive
pattern matches, but not for choosing between the alternatives that
are being considered for do notation.

All the best,
Mark






Re: MonadZero

1998-11-03 Thread Koen Claessen

Erik Meijer wrote:

 | > b) if you add an extra constructor to a single-constructor type
 | >then pattern matches on the original constructor suddenly become
 | >failable
 | 
 | That is great. I'd rather have this as a static error that getting an
 | unexpected pattern match failure in my nuclear reactor device driver:
 | 
 |data Position = Open | Close
 |controlReactor = do{ .; Open <- checkValve; ... }
 | 
 | than have this fail silently using the default definition mfail = undefined.

I agree with this completely.

Many of the proposed changes (such as renaming of the overloaded monad
operators, MonadZero, etc.) are proposed because they often bite
naive programmers.

A much-heard argument against this is: "make the error messages better".
In the case of MonadZero, I fully agree. If the compiler said:

  Type Error:
  In function: controlReactor
  Of type: Reactor ()
  Because: Reactor is not an instance of MonadZero
<= The pattern "Open" is not unfailable
<= The datatype "Position" has more than one constructor.

Nobody would complain about this, it is clear where the error comes from.

Regards,
Koen.

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






Re: MonadZero

1998-11-03 Thread Philip Wadler

Thanks for the further explanation.

  On reflection there probably shouldn't be a default declaration for mzero.
  Any compiler for Haskell must do *something* if a method is
  called for which there is neither an explicit declaration in 
  the instance, nor a default method.  ...  Leaving out the default
  method would let a compiler halt execution reporting

"Pattern match failure in `do' expression at line 39 of Foo.hs"

  which is what we want.

Well, you can't always give such a message, because the monad might be
unresolved at the point the `do' appears (as in all your examples
where MonadZero had to appear in the scope).  And you message looks
odd, since the problem is that mzero is undefined.  But these are
implementation issues.

I see the attraction of adding `mzero' to Monad.  The chief
disadvantage is that it makes the class hierarchy less expressive.  Is
there anyone out there who values the separation of Monad and
MonadZero for purposes other than `do' notation?  If not, then I
don't oppose this option.

I like Ralph's suggestion to use `fail' instead of `mzero', and
to change `fail' in IO to `raise', if that doesn't break too many
existing programs.

-- P







Re: MonadZero

1998-11-03 Thread Ralf Hinze

| > 1.Fix up the current version.
| >     use MonadZero for do expressions with *irrefutable* patterns
| > (instead of *unfailable* patterns as now)
| > 2.Nuke MonadZero altogether.
| > add mfail :: m a  to Monad instead

I opt for 2. It's certainly true that the second choice breaks existing
code, but this can easily be repaired: simply replace MonadZero by
Monad and zero by mfail (given that mfail = error "fail" is added as a
default). Right? This change is quite undramatic. And it solves a lot
of problems.





Re: MonadZero

1998-11-03 Thread Philip Wadler

Ralf says,

  Why should we introduce
  concepts (irrefutable, unfailable) only for monad expressions?

`Unfailable' was introduced explicitly for monad expressions, and I
(and many others) agree it should not be introduced just for `do'.
`Irrefutable' is already part of the language, see the Haskell report.
-- P





Re: MonadZero

1998-11-03 Thread Erik Meijer

Hi,

>Erik Meijer also spoke up vigorously in defence of MonadZero.

The reason for this is that I want the type-checker to catch as many errors
as possible.

>But the Haskell 1.4 story is unattractive becuase
> a) we have to introduce the (new) concept of unfailable

Compared to many other concepts in the report (layout rule, monomorphism
restriction, defaults, irrefutable patterns, newtype, Numeric types), this
is one of the easiest to understand.

> b) if you add an extra constructor to a single-constructor type
>then pattern matches on the original constructor suddenly become
>failable

That is great. I'd rather have this as a static error that getting an
unexpected pattern match failure in my nuclear reactor device driver:

   data Position = Open | Close
   controlReactor = do{ .; Open <- checkValve; ... }

than have this fail silently using the default definition mfail = undefined.

>The only plausible ones seem (2) [nuke MonadZero] and (5)[status quo].

I agree that these are the two plausible ones (Mark proposes (2) while
retaining MonadZero for backwards compatibility, which is better tha (2) but
still reduces static typedness).

My proposal is to stick with the status quo and make IO an instance of
MonadZero (using userError)  and MonadPlus (using catch). If users are smart
enough to define their own monads, they should be smart enough to understand
the concepts of MonadZero and failure-free matching.

Erik






Re: MonadZero

1998-11-03 Thread Philip Wadler

Simon says, 

  > Sorry, I don't understand option 2, can you please explain?

* Eliminate MonadZero
* Add 'mfail :: m a' to Monad, with a suitable default decl
* Every do expression has a type in Monad

I must be dense this morning, as I'm still in the dark.  What is the
intended meaning of `mfail'?  If `mfail' is `mzero', why change the
name?  What is the suitable default declaration?  What, if anything,
does `mfail' have to do with `do' expressions?  -- P





Re: MonadZero

1998-11-03 Thread Mark P Jones

| > 1.Fix up the current version.
| >     use MonadZero for do expressions with *irrefutable* patterns
| > (instead of *unfailable* patterns as now)
| > 2.Nuke MonadZero altogether.
| > add mfail :: m a  to Monad instead

There is another variation on 2 that you don't seem to be considering:
 - Retain MonadZero
   (So you don't break existing code using MonadZero)

 - Add mfail :: m a to Monad, with a default definition like
   mfail = error "fail", and prelude definitions of mfail = [] and
   mfail = Nothing, for lists and Maybe, respectively.
   (So everything works as you'd expect without changing user code)

 - Define the semantics of do notation solely in terms of the operators
   of the (revised) Monad class, >>=, return, and mfail.
   (So types don't change when you use tuples, add extra constructors, etc.)

A happy compromise between the alternatives you give?

All the best,
Mark





Re: MonadZero

1998-11-03 Thread Philip Wadler

Simon says,

  Here are the two proposals I suggested in
  http://research.microsoft.com/Users/simonpj
  
  > 1.Fix up the current version.
  >     use MonadZero for do expressions with *irrefutable* patterns
  > (instead of *unfailable* patterns as now)
  > 2.Nuke MonadZero altogether.
  > add mfail :: m a  to Monad instead

Sorry, I don't understand option 2, can you please explain?

Simon also says,

  But (1) really sticks in my craw.  How can we explain this:
  
  f :: Monad m => m (a,b) -> m a
  f m1 = do { x <- m1; return (fst x) }
  
  g :: MonadZero m => m (a,b) -> m a
  g m1 = do { (a,b) <- m1; return a }
  
  h :: Monad m => m (a,b) -> m a
  h m1 = do { ~(a,b) <- m1; return a }
  
  ... the type differences between g and f,h are really hard to justify.

Yes.  But these subtle differences exist independent of MonadZero.

f x  =  [fst x]
g (a,b)  =  [a]
h ~(a,b) =  [a]

Here it turns out f and h are equivalent and g differs, just as above.
All that differs with MonadZero is that the type is affected, as well
as the semantics.  Eric and others point out that this may be a good
thing: better to find out about the difference at compile-time than
at run-time.

I want to make a different plea: keep the language design consistent!
Yes, the difference between f, g, h is a wart, but let's have one wart
repeated, rather than two different warts.

-- P














RE: MonadZero

1998-11-03 Thread Simon Peyton-Jones


>   * Eliminate MonadZero
>   * Add 'mfail :: m a' to Monad, with a suitable default decl
>   * Every do expression has a type in Monad
> 
> I must be dense this morning, as I'm still in the dark.  What is the
> intended meaning of `mfail'?  If `mfail' is `mzero', why change the
> name?  What is the suitable default declaration?  What, if anything,
> does `mfail' have to do with `do' expressions?  -- P

Sorry, I was too terse.

mfail is the same as mzero.  Perhaps it should be called mzero.
The 'fail' was meant to suggest that it might not be a zero of
the monad.  (Indeed, most monad's claimed zeros do not obey the laws
for zero, because of bottom.)  I'll use mzero in what follows.

On reflection there probably shouldn't be a default declaration for mzero.
Any compiler for Haskell must do *something* if a method is
called for which there is neither an explicit declaration in 
the instance, nor a default method.   (If there is a default method
then it's the one that should be called, which is usually uninformative.)
Leaving out the default method would let a compiler halt execution
reporting

"Pattern match failure in `do' expression at line 39 of Foo.hs"

which is what we want.

> What, if anything, does `mfail' have to do with `do' expressions? 

On the other hand, if mzero *is* defined by the programmer, then it is
invoked when pattern match failure in a do-expression. Just as is 
the case with 'zero' now.


As Mark says, the whole situation is very like ordinary pattern
matching. If we have

data T = T1 Int

f :: T -> Int
f (T1 a) = a

then adding a constructor to T doesn't change the type of f,
but it might make it fail at runtime.  The interesting thing
about 'do' is that you get the chance to continue after a 
pattern match failure if you provide a binding for mzero in the
instance declaration for the monad.


The more I think about this the more I like option 2: nuke
MonadZero.

Simon





RE: MonadZero

1998-11-03 Thread Simon Peyton-Jones


>   > 2.Nuke MonadZero altogether.
>   >   add mfail :: m a  to Monad instead
> 
> Sorry, I don't understand option 2, can you please explain?

    * Eliminate MonadZero
* Add 'mfail :: m a' to Monad, with a suitable default decl
* Every do expression has a type in Monad

> Yes.  But these subtle differences exist independent of MonadZero.
> 
> f x  =  [fst x]
> g (a,b)  =  [a]
> h ~(a,b) =  [a]
> 
> Here it turns out f and h are equivalent and g differs, just as above.
> All that differs with MonadZero is that the type is affected, as well
> as the semantics.  Eric and others point out that this may be a good
> thing: better to find out about the difference at compile-time than
> at run-time.
> 
> I want to make a different plea: keep the language design consistent!
> Yes, the difference between f, g, h is a wart, but let's have one wart
> repeated, rather than two different warts.

I want consistency too.  The f,g,h you give all have the same *type*.
The f,g,h I gave do not.  It's the change in type that I object to.

It might be justifiable if the type gave new information, but it
does not.  The 'zero' can never be used; there is no justification for
changing type to MonadZero.


The status quo has two advantages
- it's the status quo
- the types are explicable

Incidentally, if we do stay with the status quo, I propose to change 'zero'
to 'mzero'?
see http://research.microsoft.com/Users/simonpj/Haskell/haskell98.html
under Prelude matters near the bottom.

Simon





MonadZero

1998-11-03 Thread Simon Peyton-Jones

Folks,

I'm working on the Haskell 98 report this week, but I'm *still*
not sure what to do about the dreaded MonadZero issue, so this message
has one last go at presenting the issues.  

Here are the two proposals I suggested in
http://research.microsoft.com/Users/simonpj

> 1.Fix up the current version.
>   use MonadZero for do expressions with *irrefutable* patterns
>   (instead of *unfailable* patterns as now)
> 2.Nuke MonadZero altogether.
>   add mfail :: m a  to Monad instead

John Hughes writes:

> You propose to choose 2. I prefer 1. Why? Apart from categorical niceties,
> 2 is a big change, highly noticeable for many users. Every monad
definition
> that uses MonadZero will have to be rewritten. 1 is much smaller: given
that
> IO is made an instance of class MonadZero, the only programs that will
need to
> change will be those which pattern-match on tuples in a do at a Monad
instance
> not in class MonadZero. Most users won't even notice this.
> 
> If 2 were clearly `right in principle' it could be right to do it anyway.
But
> I don't think the principle is clear enough here to justify the suffering.

Erik Meijer also spoke up vigorously in defence of MonadZero.  Even though
I proposed (2), I have to admit that (1) is nearer the status quo, and hence
(according to my game plan) the default choice.

But (1) really sticks in my craw.  How can we explain this:

f :: Monad m => m (a,b) -> m a
f m1 = do { x <- m1; return (fst x) }

g :: MonadZero m => m (a,b) -> m a
g m1 = do { (a,b) <- m1; return a }

h :: Monad m => m (a,b) -> m a
h m1 = do { ~(a,b) <- m1; return a }

Why must g be in MonadZero?  Because the pattern (a,b) is refutable (by
bottom).
In Haskell 1.4 g would not be in MonadZero because (a,b) is unfailable
(it can't fail to match).  But the Haskell 1.4 story is unattractive becuase
a) we have to introduce the (new) concept of unfailable
b) if you add an extra constructor to a single-constructor type
   then pattern matches on the original constructor suddenly become
failable

But the type differences between g and f,h are really hard to justify.
The 'zero' available in g is never used!  Nothing can fail.  If we force
'zero' to be available for g, when it can't be used, why not do so for 
f and h too?

There seem to be three other alternatives:
3.  Make tuples special, so that g would be in Monad, but
if we had a user-defined single-constructor type instead
then it would be in MonadZero
4.  Put all 'do' expressions in MonadZero.
5.  The status quo

(3) seems dreadful. (4) seems pointless.

The only plausible ones seem (2) [nuke MonadZero] and (5)[status quo].

Comments?

Simon





Re: MonadZero class

1996-05-14 Thread reid-alastair

Klaus (and the rest of the Haskell mailing list),

  1) I was surprised that MonadZero does not contain an operation null to
 test for the zero monad. The standard monads (lists and the Maybe type)
 and usual data structures (queues, ordered sets, ...) could easily
 implement this operation. Which other applications were intended?

I don't think we'd been thinking about queues.  Interesting idea - I
think I can see what it would look like.  

The other popular use of MonadPlus is for parsers - which could also
support a null test.

However, there's no reason to suppose that every monad with plus that
someone might think of in the future will support a null test so I'd
rather leave it out - at least until we have a lot more experience
than we do now.

[Note that the attitude of not assuming we know all possible instances
is kind of new to Haskell.  If you try defining your own Num instance,
you'll quickly find that the Num-related class hierarchy is only
really suitable for things that are basically int-like or float-like.]

  2) The library proposal does not contain any advanced data structures (yet). 
 How would one declare, for example, ordered sets as an instance of
 Monad[Plus]?

Ordered sets are a problem because constructor classes aren't up to
the job of describing the constraints (Eq, Ord, Ix, Hashable, etc) on
the elements of data structures.  The best you can do at the moment is
to use the module system and qualified names to provide libraries with
similarily interfaces.  John Peterson and I wrote about this last year
at the Haskell Workshop:

ftp://haskell.cs.yale.edu/pub/haskell/yale/libs-discussion.dvi.gz

ftp://haskell.cs.yale.edu/pub/haskell/yale/libs.dvi.gz
  -- draft companion paper which discusses the interface in more detail.
  -- note that libs.ps.gz is a MUCH OLDER version of this paper.

(You might also want to download Hugs 1.01 from any of the usual
 ftp sites.  (eg ftp.cs.nott.ac.uk)   It's more or less Haskell 1.2
 but does add constructor classes - so you could play around
 with those while waiting for a full implementation of Haskell 1.3.)

  [...] Can we expect that PreludeList will be replaced with something
  different as soon as the library proposal is extended? Will there be
  subclasses of MonadPlus?

We hope to keep the Prelude fairly stable but to let the libraries grow
as appropriate.  That said, PreludeList is perhaps the most likely to
change in future revisions.


Alastair Reid
Haskell 1.3 Committee







MonadZero class

1996-05-14 Thread Klaus Georg Barthelmann

Hi Haskell experts,
while waiting for the release of Haskell 1.3 (for my machine), I passed the time
reading the almost finished report. The most interesting part was the new monad
system. Could someone please comment on a few questions relating to the class
MonadZero?
1) I was surprised that MonadZero does not contain an operation null to test for
   the zero monad. The standard monads (lists and the Maybe type) and usual
   data structures (queues, ordered sets, ...) could easily implement this
   operation. Which other applications were intended?
2) The library proposal does not contain any advanced data structures (yet). How
   would one declare, for example, ordered sets as an instance of Monad[Plus]?
   An efficient implementation of the operation m >>= f would require that f is
   restricted to monotonous functions. (That is, x<=y implies that,
   for all x' in f(x), for all y' in f(y), x'<=y'.) As I see it, this is the
   only way to avoid unnecessary comparisons in filter, using the fact that
   return is monotonous in this sense.
   The constraint for f looks as if it could be explained by a category
   theorist. But the books and articles I have seen on the subject only deal
   with the special case join = (>>= id) instead of (>>=).
3) It would be nice if operations like elem, foldl, foldr and others could be
   overloaded in a similar manner. Can we expect that PreludeList will be
   replaced with something different as soon as the library proposal is
   extended? Will there be subclasses of MonadPlus?
Best regards,
  Klaus

Klaus Barthelmann, Institut f"ur Informatik, Universit"at Mainz, Germany,
[EMAIL PROTECTED]