RE: ">>" and "do" notation

2002-04-03 Thread Simon Peyton-Jones


|   > I think the point that's being missed in this discussion
|   > is that a monad is a n *abstract* type, and sometimes the
|   > natural "equality" on the abstract type is not the same as
|   > equality on representations. ... If we can give >> a 
| more efficient
|   > implementation, which constructs a better representation
|   > than >>= does, that's fine, as long as the two
|   > representations "mean" the same thing.
| 
|   Point taken, but I remain unconvinced. What comes out of the
|   monad /isn't/ abstract; there's nothing to ensure that
|   subsequent use respects the abstraction.
| 
| That's true, of course. But *should* we insist that the 
| programming language guarantee that abstractions are always 
| respected? i.e. equivalent representations are always treated 
| equivalently? 

This is an interesting discussion but from the point of view of H98 I'm 
interested in answering the following much narrower question:

what should be the desugaring of 
do { e ; Q }

The current Report uses (>>) for this, and (>>=) for the "p <- e" case.
An alternative would be to use (>>=) for both.

I take it for granted that (>>) stays as an operation of class Monad:
several people have argued for this, and I have no intention of changing
H98 in that respect.

I take it for granted that if the Report says "use >>" then
implementations
should.  So either GHC and Hugs have to change or the Report does.


So the question remains: what would be best for programmers:

A: the predictability that desugaring do-notation 
uses only (>>=) and return, or

B: or the extra power of using (>>) for the no-patterns case?

If there are Good Reasons for having (>>) in the class, as several
have argued, then I guess we should go for (B).  In that case the Report
would stay unchanged, and the impls would have to change.  I also
thought that James's analogy of (-x) translating to (negate x) and not
to (0-x) was a good one.

I originally favoured (A) but I'm happy to go with (B).

anyone disagree?

Simon
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: ">>" and "do" notation

2002-04-03 Thread John Hughes


> I think the point that's being missed in this discussion
> is that a monad is a n *abstract* type, and sometimes the
> natural "equality" on the abstract type is not the same as
> equality on representations. ... If we can give >> a more efficient
> implementation, which constructs a better representation
> than >>= does, that's fine, as long as the two
> representations "mean" the same thing.

Point taken, but I remain unconvinced. What comes out of the
monad /isn't/ abstract; there's nothing to ensure that
subsequent use respects the abstraction.

That's true, of course. But *should* we insist that the programming language
guarantee that abstractions are always respected? i.e. equivalent
representations are always treated equivalently? We don't always in other
contexts. To take an example, consider a bag datatype with a bagFold operator
and an Eq instance that implements bag equality. Then

xBag == yBag

doesn't necessarily imply

bagFold op z xBag == bagFold op z yBag

We rely on the programmer to use bagFold properly, i.e. supply an AC op with
unit z. If he doesn't, the abstraction is broken.

> This is all perfectly respectable, and has to do with the
> fact that Haskell i s a programming language, not
> mathematics -- so we represent equivalence classe s by
> values chosen from them. For the *language* to rule out
> constructing different representations for "equivalent"
> constructions, such as >> and >>=, would be unreasonable.

Here's the problem. Your argument sounds very similar to the
one against type checking. That /you/ can get it right
doesn't encourage me to believe that J Random Hacker isn't
going to abuse the facility. It's not as if you couldn't
define >!= and >! for something that's nearly a monad, it
would just stop you using the do notation, which is, I think
fair, since Haskell provides no way of selecting the correct
form of equality for do {_ <- A; B} == do {A; B}.

  Jón

This is a much bigger cost than you make out. Making something into a monad
allows not only the use of the do syntax, it allows the use of a large number
of generic monad operations, the application of monad transformers, etc
etc. It's a big deal.

I agree there's an analogy here with type-checking here. Indeed, there's a
tradeoff where typechecking is concerned too: we give up some flexibility for
greater safety. We accept that nowadays, because the flexibility we give up
with Hindley-Milner typing is not so great, and the gain in safety is
considerable. But would you argue that we should prohibit programs which
potentially break an abstraction?  I.e. prohibit bagFold, or alternatively
allow it only for operators which the compiler can *decide* are AC? Would you
want to prohibit monad instances which the compiler cannot decide satisfy the
monad laws? I know you would want to prohibit monad instances where the
compiler cannot decide that >> and >>= are properly related.

The trouble is that prohibiting bagFold, separate definitions of >>,
etc. altogether is quite a big cost: such things are very useful! Yet we lack
the analogue of the Hindley-Milner type system -- a way for the compiler to
*decide* that a monad instance, an ADT definition, or whatever, is OK, which
is *proven* sufficiently flexible to handle almost all practical cases. In its
absence, the analogy with type-checking is not compelling. If all we had was a
monomorphic type system, then I would be against imposing type-checking too.

Perhaps there's an interesting research direction here for somebody...

John

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: ">>" and "do" notation

2002-04-02 Thread Dylan Thurston

On Tue, Apr 02, 2002 at 08:48:41PM +0100, Jon Fairbairn wrote:
> Point taken, but I remain unconvinced. What comes out of the
> monad /isn't/ abstract; there's nothing to ensure that
> subsequent use respects the abstraction.

Sure.  That's the programmer's responsibility to keep track of.  To me
the situation seems entirely analogous to defining a '+' operation that
is not associative; if the programmer wants to do it, more power to her.
(In fact, the standard '+' on floating point numbers is not
associative.  Sometimes it matters!)

These considerations are the reasons compilers are typically prohibited
from taking advantage of such laws, and why the translation from the
'do' notation should be the obvious one (using '>>').

Best,
Dylan Thurston



msg10610/pgp0.pgp
Description: PGP signature


Re: ">>" and "do" notation

2002-04-02 Thread Jon Fairbairn

On Tue, 2 Apr 2002 10:00:37 +0200 (MET DST), John Hughes
<[EMAIL PROTECTED]> wrote:
>   >If (as a human reader of a programme) I see
>   >
>   >do a <- thing1
>   >   
>   >
>   >and I notice (perhaps after some modifications) that a is
>   >not present in , then I /really/ don't want a
>   >change to
>   >
>   >do thing1
>   >   
>   >
>   >to change the meaning of the programme.

> I think the point that's being missed in this discussion
> is that a monad is a n *abstract* type, and sometimes the
> natural "equality" on the abstract type is not the same as
> equality on representations. Of course, we want the left
> and right hand sides of the monad laws to have the same
> "meaning", and we want >> to "mean" >>= \_ ->, but this
> meaning is really up to the abstract equality, not the
> concrete one. If we can give >> a more efficient
> implementation, whic h constructs a better representation
> than >>= does, that's fine, as long as the two
> representations "mean" the same thing.

Point taken, but I remain unconvinced. What comes out of the
monad /isn't/ abstract; there's nothing to ensure that
subsequent use respects the abstraction.

> To be specific, the application that kicked off this
> discussion was program generation. In this example, it's
> not important that >> and >>= generate the same *program
> text*, the important thing is that they generate
> equivalent programs. If >> can more easily generate a more
> efficient program, that's fine.

Is it fine though?  Since it will be possible to inspect the
generated code, it's possible that a change from do {_ <- A;
B} to do {A; B} can radically alter the subsequent behaviour
of the programme.

> There's another example in QuickCheck, where we use a
> monad Gen for random value generation -- Gen a is a
> generator for random values of type a. Gen doe s not
> satisfy the monad laws: for example, g and g >>= return
> will usually generate different values. But viewed as
> *probability distributions* (which i s how we think of
> them), they are the same. "Morally", Gen is a monad.

Well, aren't there cases where generating the /same/
pseudo-random sequences is important? In such a case, making
what looks like a semantically neutral change to the
programme might invalidate years of stored results.

> This is all perfectly respectable, and has to do with the
> fact that Haskell i s a programming language, not
> mathematics -- so we represent equivalence classe s by
> values chosen from them. For the *language* to rule out
> constructing different representations for "equivalent"
> constructions, such as >> and >>=, would be unreasonable.

Here's the problem. Your argument sounds very similar to the
one against type checking. That /you/ can get it right
doesn't encourage me to believe that J Random Hacker isn't
going to abuse the facility. It's not as if you couldn't
define >!= and >! for something that's nearly a monad, it
would just stop you using the do notation, which is, I think
fair, since Haskell provides no way of selecting the correct
form of equality for do {_ <- A; B} == do {A; B}.

  Jón


-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: ">>" and "do" notation

2002-04-01 Thread John Hughes


>If (as a human reader of a programme) I see
>
>do a <- thing1
>   
>
>and I notice (perhaps after some modifications) that a is
>not present in , then I /really/ don't want a
>change to
>
>do thing1
>   
>
>to change the meaning of the programme.

I think the point that's being missed in this discussion is that a monad is an
*abstract* type, and sometimes the natural "equality" on the abstract type is
not the same as equality on representations. Of course, we want the left and
right hand sides of the monad laws to have the same "meaning", and we want >>
to "mean" >>= \_ ->, but this meaning is really up to the abstract equality,
not the concrete one. If we can give >> a more efficient implementation, which
constructs a better representation than >>= does, that's fine, as long as the
two representations "mean" the same thing.

To be specific, the application that kicked off this discussion was program
generation. In this example, it's not important that >> and >>= generate the
same *program text*, the important thing is that they generate equivalent
programs. If >> can more easily generate a more efficient program, that's
fine.

There's another example in QuickCheck, where we use a monad Gen for random
value generation -- Gen a is a generator for random values of type a. Gen does
not satisfy the monad laws: for example, g and g >>= return will usually
generate different values. But viewed as *probability distributions* (which is
how we think of them), they are the same. "Morally", Gen is a monad.

This is all perfectly respectable, and has to do with the fact that Haskell is
a programming language, not mathematics -- so we represent equivalence classes
by values chosen from them. For the *language* to rule out constructing
different representations for "equivalent" constructions, such as >> and >>=,
would be unreasonable.

John Hughes
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



On the subject of monads (was Re: ">>" and "do" notation)

2002-03-31 Thread Jay Cox

On Sat, 30 Mar 2002, Richard Uhtenwoldt wrote:

> The bottom line is a social one: language communities compete fiercely
> for programmers.  There is no shortage of languages with open-sourced
> implementations in which James could have written his program.  (Er,
> actually James is embedding a DSL in Haskell, which brings many
> programmers to Haskell.)  If we want Haskell to grow, we must make
> it as easy as possible for programmers to solve their problems in
> Haskell.
>
> Of course there are some things that are essential to Haskell that we
> should not compromise on.  Those who describe a >> b = a >>= \_ -> b
> as a law might maintain that it is one of those essential things.
> Well, to them I ask, are id x = x and const x y = y laws, too?  How
> about fix f = f (fix f)?  swap (a,b) = (b,a)?
>
> mirror (Right a) = Left a
> mirror (Left a) = Right a?

This brings up a point in my mind. What should one do instances of the
class Monad which might violate some monad law?

THE MONAD LAWS [1]

1. return a >>= k= k a
2. m >>= return  = m
3. m >>= (\x -> k x >>= h)   = (m >>= k) >>= h



long discursion begins, go down far below to see my point 


I was going to have a section in the Strictness FAQ I'm writing which
gives examples why lazy evaluation rocks, so to remind the readers that
there are reasons for haskell using a lazy evaluation strategy.  (I'm sad
to say that this is one of sections I don't think I'll complete to the
point of releasing anytime soon.)

Here's the long story of one of the examples I'm contemplating.

I one day came across this idea for a monad.

For background, the list (nondeterminism) monad is defined as something
like [2]

instance Monad [] where
  return x = [x]
  >>=  = bindL

  [] `bindL` f = []
  (x:xs) `bindL` f = f x ++ (xs `bindL` f)

this looks equivalant to the Haskell reports definition for >>=
  m >>= k  = concat (map k m)


I suppose this is (partially) used to define the list comprehensions we
grew to like so well, and you can use those to write expressions almost
like you could query a database, or give all possible scenarios, or
whatever.

One problem with this definition may be that you can only find out all
possible scenarios for finite lists only (except for the first binded
list, which could be infinite.

Example.

[(a,b,c) | a<-[1..],b<-[True,False],c<-"Cheeze Whiz"]

Analyzing the above definition you may find that the cuprit is (++).  So,
what's another way to join two lists so that members of both lists will
eventially be found in the combined list?  Interweave them! [3].

>interleave [] l' = l'
>interleave (x:xs) l' = x :interleave l' xs

So you might think that all you have to do is switch  `interleave`
for (++) and you have this new, powerful monad that allows you
to combine elements from anysize lists (countable or finite) and generate
every expression thereof.

>unC1 (C1 x) = x
>newtype C1 a = C1 [a]
>
>instance Monad C1 where
>  return x = C1 [x]
>  (C1 [])  >>= f = C1 []
>  (C1 (x:xs))  >>= f = C1 $
> unC1 (f x) `interleave` unC1 (C1 xs >>= f)
>
>allnats = [1..]::[Integer]
>
>-- generate_all_integers
>-- use C1 constructor so we can use that monad instance.
>
>g = C1 (0:(interleave allnats (map negate allnats)))
>
>all_integral_3dpoints = unC1 $
>do x<-g
>   y<-g
>   z<-g
>   return (x,y,z)
>--give all points that have a integral distance from the origion
>
>anyzero (0,_,_) = True
>anyzero (_,0,_) = True
>anyzero (_,_,0) = True
>anyzero _ = False

>points = filter (issquare . (\(x,y,z) -> x^2+y^2+z^2))
>  $ filter (not . anyzero) all_integral_3dpoints
>

  definition of issquare, a predicate which determines if
a integer is the square of another, is left up to
the imagination of the reader

>main = print $ (take 10 points)

We'll call it a Cantor Monad for lack of imagination (Cantor is the
mathematician that is associated with the many concepts of infinity
and countablility)



And you are all good and happy.  The only problem is, you HAVEN'T DEFINED
A MONAD!  It disobeys the monad associativity law!



That is, it violates this [1]

m >>= (\x -> k x >>= h)   = (m >>= k) >>= h

(or to restate this)

do x <- m;y <-k x; h y= do y<- (do x <- m; k x); h y

This can be checked by seeing that list1 is not equal to list2 in this
snippit.



>k x = do y<-g
> return (x,y)
>h (x,y) = do z<-g
> return (x,y,z)

>list1 = unC1 $ g >>= (\x-> k x >>= h)
>list2 = unC1 $ (g >>= k)>>= h

>main =
>do print "first list"
>   print (take 10 list1)
>   print "second list"
>   print (take 10 list2)



(whew! this is a long message!)

However, I am not completely certain as to a verifiable proof of what I am
about to say, but I'm very certain that you could say that list1 is SET
equal to list 2, in otherwords, every element in list2 is in list2, and
vis

Re: ">>" and "do" notation

2002-03-30 Thread Richard Uhtenwoldt

>If (as a human reader of a programme) I see
>
>do a <- thing1
>   
>
>and I notice (perhaps after some modifications) that a is
>not present in , then I /really/ don't want a
>change to
>
>do thing1
>   
>
>to change the meaning of the programme.

That's understandable, just like it's understandable that a programmer
does not want to read a program that redefines id or const or map to
something with a completely different meaning.  But is that any reason
for the language standard to *disallow* redefinition of id or const or
map?

And if the answer is yes, where does this proscriptive zeal stop?
Should the language standard, eg, disallow functions whose name ends
in 'M' but do not have monads in their signature?

No: the individual programmer should be free to decide to override
conventions if doing that is expedient.  After all, there is no
danger that what James wants to do will become common or widespread;
it's just an expediency to deal with a rare situation.

The bottom line is a social one: language communities compete fiercely
for programmers.  There is no shortage of languages with open-sourced
implementations in which James could have written his program.  (Er,
actually James is embedding a DSL in Haskell, which brings many
programmers to Haskell.)  If we want Haskell to grow, we must make
it as easy as possible for programmers to solve their problems in
Haskell.

Of course there are some things that are essential to Haskell that we
should not compromise on.  Those who describe a >> b = a >>= \_ -> b
as a law might maintain that it is one of those essential things.
Well, to them I ask, are id x = x and const x y = y laws, too?  How
about fix f = f (fix f)?  swap (a,b) = (b,a)?

mirror (Right a) = Left a
mirror (Left a) = Right a?

etc, etc.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: ">>" and "do" notation

2002-03-29 Thread Jon Fairbairn

Wolfgang Jeltsch <[EMAIL PROTECTED]> wrote:
> It shouldn't be syntactic suger but at most an operator which does not belong
> to the monad class. One could define (>>) just as an ordinary function
> instead of a class member.

That sounds to me like the best idea so far. 

If (as a human reader of a programme) I see

do a <- thing1
   

and I notice (perhaps after some modifications) that a is
not present in , then I /really/ don't want a
change to

do thing1
   

to change the meaning of the programme.


  Jón


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: ">>" and "do" notation

2002-03-28 Thread Wolfgang Jeltsch

On Thursday, March 28, 2002, 16:37 CET James B. White III wrote:
> [...]
> I think the default definition of ">>" is just that, a default, and not a
> law.

I suppose, a >> b = a >>= \_ -> b is intended to be a law. This would mean
that every redefined (>>) would have to obey this law.

> [...]
> If it is a law, why are users given the power to change it!

For performance reasons, I would suppose.

> Also, I think that the Report *specifies* the translation of "do" to ">>",
> not merely suggests it.

The report specifies certain identities and suggests to use these identities
for translations into the kernel. If it is also a law that a >> b and a >>=
\_ -> b are identical even with respect to laziness then, I think, a
conforming Haskell implementation could use the latter instead of the former
to realize do expressions. But I would prefer implementations using (>>).

> [...]
> ">>" should no longer be a class function with a default value that can be
> changed; it should be syntactic sugar built into Haskell, like "do"
> notation.

It shouldn't be syntactic suger but at most an operator which does not belong
to the monad class. One could define (>>) just as an ordinary function
instead of a class member.

> [...]

By the way, why uses the report the complicated looking \_ -> b instead of
just const b.

Wolfgang

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell