strictly matching monadic let and overloaded Bool (was: Are pattern guards obsolete?)

2006-12-14 Thread Claus Reinke

consider the following examples:

   -- do-notation: explicit return; explicit guard; monadic result 
   d _ = do { Just b - return (Just True); guard b; return 42 }


   -- list comprehension: explicit return; implicit guard; monadic (list) result
   lc _ = [ 42 | Just b - return (Just True), b ]

   -- pattern guard: implicit return; implicit guard; non-monadic result
   pg _ | Just b - Just True, b = 42


This ongoing discussion has made me curious about whether we could actually
get rid of these irregularities in the language, without losing any of the 
features
we like so much.

=== attempt 1

(a) boolean statements vs guards

   this looks straightforward. Bool is a type, so can never be an instance of
   constructor class Monad, so a boolean statement in a monadic context is
   always invalid at the moment. that means we could simply extend our
   syntactic sugar to take account of types, and read every

((e :: Bool) :: Monad m = m _) 
   
   in a statement of a do block as a shorthand for


   (guard (e :: Bool) :: Monad m = m ())
   
(b) missing return in pattern guards


   this could be made to fit the general pattern, if we had (return == id).
   that would put us into the Identity monad, which seems fine at first,
   since we only need return, bind, guard, and fail. unfortunately, those
   are only the requirements for a single pattern guard - to handle not
   just failure, but also fall-through, we also need mplus. which means
   that the Identity monad does not have enough structure, we need at
   least Maybe..

this first attempt leaves us with two problems. not only is (return==id)
not sufficient for (b), but the suggested approach to (a) is also not very
haskellish: instead of having syntactic sugar depend on type information,
the typical haskell approach is to have type-independent sugar that 
introduces overloaded operations, such as 


   fromInteger :: Num a = Integer - a

to be resolved by the usual type class machinery. addressing these two 
issues leads us to


=== attempt 2

(a) overloading Bool

following the approach of Num and overloaded numeric literals, we could
introduce a type class Boolean

   class Boolean b where
   fromBool :: Bool - b

   instance Boolean Bool where 
   fromBool = id


and implicitly translate every literal expression of type Bool

   True ~~ fromBool True
   False ~~ fromBool False

now we can embed Boolean statements as monadic statements simply by
defining an additional instance

   instance MonadPlus m = Boolean (m ()) where
   fromBool = guard

(b) adding a strictly matching monadic let

we can't just have (return==id), and we do not want the hassle of having to
write

   pattern - return expr

in pattern guards. the alternative of using let doesn't work either

   let pattern = expr

because we do want pattern match failure to abort the pattern guard and
lead to overall match failure and fall-through. so what we really seem to want 
is a shorthand notation for a strict variant of monadic let bindings. apfelmus 
suggested to use '=' for this purpose, so that, wherever monadic generators

are permitted

   pattern = expr  ~~ pattern - return expr

===

returning to the examples, the approach of attempt 2 would allow us to write

   -- do-notation: implicit return; implicit guard; monadic result 
   d _ = do { Just b = Just True; b; return 42 }


   -- list comprehension: implicit return; implicit guard; monadic (list) result
   lc _ = [ 42 | Just b = Just True, b ]

   -- pattern guard: implicit return; implicit guard; non-monadic result
   pg _ | Just b = Just True, b = 42

almost resolving the irregularities, and permitting uniform handling of related
syntactic constructs. hooray!-)

I say almost, because Bool permeates large parts of language and libraries,
so one would need to check every occurence of the type and possibly
replace Bool by (Boolean b = b). the Boolean Bool instance should mean
that this process could be incremental (ie, even without replacements, things
should still work, with more replacements generalizing more functionality,
similar to the Int vs Integer issue), but that hope ought to be tested in 
practice.

one issue arising in practice is that we would like to have

   fromBool  :: MonadPlus m = Bool - m a

but the current definition of guard would fix the type to

   fromBool  :: MonadPlus m = Bool - m ()

which would require type annotations for Booleans used as guards. see the
attached example for an easy workaround.

on the positive side, this approach would not just make pattern guards more
regular, but '=' and 'MonadPlus m = Boolean (m ()) would be useful for 
monadic code in general. even better than that, those of use doing embedded

DSLs in Haskell have been looking for a way to overload Bools for a long
time, and the implicit 'Boolean b = fromBool :: Bool - b' ought to get us
started in the right direction. most likely, we would need more Bool-based
constructs to be overloaded for 

Re: Are pattern guards obsolete?

2006-12-13 Thread Yitzchak Gale

Donald Bruce Stewart [EMAIL PROTECTED] wrote:

The joy of pattern guards
reveals once you have more conditions.


I wrote:

Of course, this is not really the joy of
pattern guards. It is the joy of monads,
with perhaps a few character strokes
saved by a confusing overloading of (-).


Philippa Cowderoy wrote:

I don't find it any more confusing than the overloading
of -.


You mean that it is used both for lambda abstractions
and for functional dependencies? True, but those
are so different that there is no confusion.


Note that it's not (-) - it's not an operator.


Right, it is syntactic sugar for a monad.

But this syntax is already used in two places:
do notation and list comprehensions. The semantics
are exactly the same in both existing uses.

The semantics of the proposed new use in pattern
guards is quite different, as was discussed in the
previous thread. Yet close enough to be confused.

There seems to be a consensus that pattern guards
are here to stay. So I am proposing to mitigate the
damage somewhat by using a different but similar
symbol . That matches the different but similar
semantics. I mentioned (-) as one possibility.

Regards,
Yitz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Are pattern guards obsolete?

2006-12-13 Thread Philippa Cowderoy
On Wed, 13 Dec 2006, Yitzchak Gale wrote:

 Yitzchak Gale wrote:
   Of course, this is not really the joy of
   pattern guards. It is the joy of monads,
   with perhaps a few character strokes
   saved by a confusing overloading of (-).
 
 Philippa Cowderoy wrote:
  I don't find it any more confusing than the overloading
  of -.
 
 You mean that it is used both for lambda abstractions
 and for functional dependencies? True, but those
 are so different that there is no confusion.
 

You missed out case statements.

-- 
[EMAIL PROTECTED]

My religion says so explains your beliefs. But it doesn't explain
why I should hold them as well, let alone be restricted by them.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Are pattern guards obsolete?

2006-12-13 Thread Philippa Cowderoy
On Wed, 13 Dec 2006, Yitzchak Gale wrote:

 Philippa Cowderoy wrote:
   I don't find it any more confusing than the overloading
   of -.
 
 I wrote:
  You mean that it is used both for lambda abstractions
  and for functional dependencies? True, but those
  are so different that there is no confusion.
 
 Oh, and case. Also quite different.

This is what I get for replying straight away!

 Anyway, existing problems are not an excuse to
 repeat the mistake and make matters even worse.
 

I think my point is that I'm not aware of many people who actually think 
this is a problem or get confused.

-- 
[EMAIL PROTECTED]

There is no magic bullet. There are, however, plenty of bullets that
magically home in on feet when not used in exactly the right circumstances.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Are pattern guards obsolete?

2006-12-13 Thread Yitzchak Gale

Philippa Cowderoy wrote:

This is what I get for replying straight away!


Oh, no, I'm happy that you responded quickly.


I think my point is that I'm not aware of many people
who actually think this is a problem or get confused.


Well, I don't mean that this is something that experienced
Haskell programmers will stop and scratch their heads
over.

But the more of these kinds of inconsistencies you have,
the worse it is for a programming language. The effect
is cumulative. When there are too many of them, they make
the language feel heavy, complex, and inelegant. They
increase the number of careless errors. They put
off beginners.

Regards,
Yitz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Are pattern guards obsolete?

2006-12-13 Thread Iavor Diatchki

Hi,

I am not clear why you think the current notation is confusing...
Could you give a concrete example?  I am thinking of something along
the lines:  based on how - works in list comprehensions and the do
notation, I would expect that pattern guards do XXX but instead, they
confusingly do YYY.  I think that this will help us keep the
discussion concrete.

-Iavor


On 12/13/06, Yitzchak Gale [EMAIL PROTECTED] wrote:

Philippa Cowderoy wrote:
 This is what I get for replying straight away!

Oh, no, I'm happy that you responded quickly.

 I think my point is that I'm not aware of many people
 who actually think this is a problem or get confused.

Well, I don't mean that this is something that experienced
Haskell programmers will stop and scratch their heads
over.

But the more of these kinds of inconsistencies you have,
the worse it is for a programming language. The effect
is cumulative. When there are too many of them, they make
the language feel heavy, complex, and inelegant. They
increase the number of careless errors. They put
off beginners.

Regards,
Yitz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


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


Re: Are pattern guards obsolete?

2006-12-13 Thread apfelmus
Iavor Diatchki wrote:
 I am not clear why you think the current notation is confusing...
 Could you give a concrete example?  I am thinking of something along
 the lines:  based on how - works in list comprehensions and the do
 notation, I would expect that pattern guards do XXX but instead, they
 confusingly do YYY.  I think that this will help us keep the
 discussion concrete.

Pattern guards basically are a special-case syntactic sugar for
(instance MonadPlus Maybe). The guard

foo m x
| empty m = bar
| Just r - lookup x m, r == 'a' = foobar

directly translates to

foo m x = fromMaybe $
   (do { guard (empty m); return bar;})
 `mplus`
   (do {Just r - return (lookup m x); guard (r == 'a');
   return foobar;})

The point is that the pattern guard notation

Just r - lookup m x

does *not* translate to itself but to

Just r - return (lookup m x)

in the monad. The - in the pattern guard is a simple let binding. There
is no monadic action on the right hand side of - in the pattern guard.
Here, things get even more confused because (lookup m x) is itself a
Maybe type, so the best translation into (MonadPlus Maybe) actually would be

r - lookup m x


Regards,
apfelmus

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


Re: Are pattern guards obsolete?

2006-12-13 Thread Claus Reinke

I am not clear why you think the current notation is confusing...
Could you give a concrete example?  I am thinking of something along
the lines:  based on how - works in list comprehensions and the do
notation, I would expect that pattern guards do XXX but instead, they
confusingly do YYY.  I think that this will help us keep the
discussion concrete.


consider the following examples:

   -- do-notation: explicit return; explicit guard; monadic result 
   d _ = do { Just b - return (Just True); guard b; return 42 }


   -- list comprehension: explicit return; implicit guard; monadic (list) result
   lc _ = [ 42 | Just b - return (Just True), b ]

   -- pattern guard: implicit return; implicit guard; non-monadic result
   pg _ | Just b - Just True, b = 42

in spite of their similarity, all of these constructs handle some of the 
monadic aspects differently. the translations of pattern guards not only

embed statements in guard, they also embed the right hand sides of
generators in return. translations of list comprehensions only lift 
statements. translation of do-notation lifts neither statements nor

generators.

does this clarify things?

Claus

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


Re: Are pattern guards obsolete?

2006-12-13 Thread Neil Mitchell

Hi


in spite of their similarity, all of these constructs handle some of the
monadic aspects differently. the translations of pattern guards not only
embed statements in guard, they also embed the right hand sides of
generators in return. translations of list comprehensions only lift
statements. translation of do-notation lifts neither statements nor
generators.

does this clarify things?


No. Pattern guards are obvious, they could only work in one
particular way, and they do work that way. They make common things
easier, and increase abstraction. If your only argument against them
requires category theory, then I'd say that's a pretty solid reason
for them going in.

The argument that people seem to be making is that they are confusing,
I completely disagree.

f value | Just match - lookup value list = g match

Without thinking too hard, I am curious how anyone could get the
meaning of this wrong if they understand the rest of Haskell. Can you
show a concrete example, where you think a user would get confused?

Thanks

Neil
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Are pattern guards obsolete?

2006-12-13 Thread Dave Menendez
Yitzchak Gale writes:

 Philippa Cowderoy wrote:
  I don't find it any more confusing than the overloading
  of -.
 
 I wrote:
  You mean that it is used both for lambda abstractions
  and for functional dependencies? True, but those
  are so different that there is no confusion.
 
 Oh, and case. Also quite different.

Also type and kind signatures.

The use in case and lambda abstractions strike me as analogous. They
both have a pattern to the left and an expression to the right.
-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Are pattern guards obsolete?

2006-12-12 Thread Yitz Gale
Donald Bruce Stewart [EMAIL PROTECTED] writes:
 The joy of pattern guards
 reveals once you have more conditions.

Of course, this is not really the joy of
pattern guards. It is the joy of monads,
with perhaps a few character strokes
saved by a confusing overloading of (-).

But some people do seem to be used to this
notation by now. So perhaps a good compromise
would be to use a different operator for pattern
guards, e.g. (-), instead of (-).

What do you say?

Yitz

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


Re: Are pattern guards obsolete?

2006-12-12 Thread Philippa Cowderoy
On Wed, 13 Dec 2006, Yitz Gale wrote:

 Donald Bruce Stewart [EMAIL PROTECTED] writes:
  The joy of pattern guards
  reveals once you have more conditions.
 
 Of course, this is not really the joy of
 pattern guards. It is the joy of monads,
 with perhaps a few character strokes
 saved by a confusing overloading of (-).
 

I don't find it any more confusing than the overloading of -. Note that 
it's not (-) - it's not an operator.

-- 
[EMAIL PROTECTED]

Sometimes you gotta fight fire with fire. Most
of the time you just get burnt worse though.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime