Re: A new view of guards

1997-04-29 Thread Manuel Chakravarty

> I would really welcome feedback on this proposal.  Have you encountered
> situations in which pattern guards would be useful?  Can you think of ways
> in which they might be harmful, or in which their semantics is non-obvious?
> Are there ways in which the proposal could be improved?  And so on.

On first reading, I don't have any suggestions, but I fully agree that
the mentioned clunky function definitions are a nuisance and occur
often. The proposed syntax may look a bit strange in the beginning,
but I find the upward compatibility and the simple changes to the
grammar very attractive.

Manuel






Re: A new view of guards

1997-04-29 Thread Heribert Schuetz

I found Simon Peyton Jones' proposal for guarded equations very
interesting and convincing. However, I see situations where yet more
flexibility in guarded expressions would be useful, and I have included
a suggestion for an extension below. I hope the following is
understandable and makes sense, although it is certainly not the product
of as deep considerations as those underlying Simon Peyton Jones'
proposal.

Heribert Schutz.


An Example
--

Consider a type for arithmetic expressions that consist of constants,
variables, and a binary addition operation:

  data Expr = Val Integer | Var String | Plus Expr Expr

We want to simplify such an expression by removing superfluous zeroes.
This can be implemented in today's Haskell as follows:

  -- version 1
  simplify (Plus e e')  = case s of
(Val 0) -> s'
_   -> case s' of
 (Val 0) -> s
 _   -> (Plus s s')
where
s  = simplify e
s' = simplify e'
  simplify e= e

Many of Simon Peyton Jones' considerations about "clunky" also hold for
"simplify". For example, as in the "clunky" example, we can avoid the
case expressions by introducing a helper function:

  -- version 2
  simplify (Plus e e') = simplify_plus (simplify e) (simplify e')
where simplify_plus (Val 0) s'   = s'
  simplify_plus s   (Val 0)  = s
  simplify_plus s   s'   = Plus s s'
  simplify e   = e


The Problem
---

We can avoid both the case expressions and the helper function by Simon
Peyton Jones' guard syntax

  -- version 3
  simplify (Plus e e') | s  <- simplify e ,
 s' <- simplify e',
 (Val 0) <- s   = s'
   | s  <- simplify e ,
 s' <- simplify e',
 (Val 0) <- s'  = s
   | s  <- simplify e ,
 s' <- simplify e'  = (Plus s s')
  simplify e= e

but perhaps this is not what we want: We might not want to replicate the
expressions "simplify e" and "simplify e'".

The problem lies in the "linearity" of qualifier lists.  If any
qualifier fails, then the *entire* qualifier list fails and the next
guard (or the next equation) is tried.  It is not possible to backtrack
just a part of the list and to try alternatives for those qualifiers
over which we have backtracked.


A Solution
--

Therefore I would suggest some sort of "nested" qualifiers. I have not
thought much about syntax, but I hope that the following code is
sufficiently intuitive for understanding the idea:

  -- version 4
  simplify (Plus e e') | s  <- simplify e ,
 s' <- simplify e'  | (Val 0) <- s  = s'
| (Val 0) <- s' = s
| otherwise = (Plus s s')
  simplify e= e

The second "|" indicates that failure of the qualifier "(Val 0) <- s"
should not lead to backtracking over the entire guard (and continuing
with the last equation), but only to the second "|". Pattern matching
continues with the third "|", which appears on the same nesting level.
(I have tried to hint at this by using the same indentation, but as I
said before, the syntax is not the essential point of the idea.) If the
qualifier "(Val 0) <- s'" fails as well, the "otherwise" case is chosen.

In this example the entire guard (from the first "|" to "otherwise")
cannot fail, because the first two qualifiers have failure-free patterns
on the left hand side and the last qualifier is an "alternative
qualifier" including "otherwise". But if any of the qualifiers were
modified in such a way that they can fail, then it would make sense to
add an alternative to this guard. This alternative would start with a
"|" under the first "|", just before the last equation.


Miscellaneous Remarks
-

- Can we expect a compiler to recognize common prefixes of
  "Peyton-Jones-style" guards? If so, then one might prefer the style of
  coding as given in version 3, according to the consideration that we
  can "write down the cases we want to consider, one at a time,
  independently of each other." (Quoted from Simon Peyton Jones' note.)

  But one might also prefer a style where the common prefixes of the
  qualifier lists are "factored out" as in version 4. This is then
  similar to the possibility to factor out the parameter matching before
  the guards.

- Something like these nested qualifiers might also be interesting for
  monad comprehensions and do expressions (of course only for instances
  of MonadPlus). But there we already have the possibility of nesting
  and using "++" on the right hand side of a "<-" qualifier.

- Nested qualifiers would become superfluous if we modified Simon Peyt

Re: A new view of guards

1997-04-29 Thread Simon L Peyton Jones



| We can avoid both the case expressions and the helper function by Simon
| Peyton Jones' guard syntax
| 
|   -- version 3
|   simplify (Plus e e') | s  <- simplify e ,
|s' <- simplify e',
|(Val 0) <- s   
|  = s'
|| s  <- simplify e ,
|s' <- simplify e',
|(Val 0) <- s' 
|  = s
|| s  <- simplify e ,
|s' <- simplify e'
|  = (Plus s s')
|   simplify e   = e

I agree with the general thrust of your message (though I was unable to
think of a good syntax for it), but in this particular case there's no
problem.  A where clause will do nicely:

   simplify (Plus e e') | (Val 0) <- s  = s'
| (Val 0) <- s' = s
| otherwise = Plus s s'
where
  s  = simplify e
  s' = simplify e'

simplify e  = e






Re: A new view of guards

1997-04-29 Thread John Launchbury

I love Simon's suggestion. It gives me all the right vibes. And <- seems to
me to be the right connective to use.

At the risk of beating my hobby horse, let's not think of <- solely in
terms of monads. It is certainly appropriate there, but it is also
appropriate for lists when thought of purely as a bulk data type, and I
think it's appropriate here also.

Simon's syntax also provides a viable alternative to @ patterns

  f x @ (Just 3) y = e

  f x y | Just 3 <- x = e

though it is slightly less convenient in certain contrived examples (but
very much less ad hoc).

John.







Re: A new view of guards

1997-04-29 Thread Alex Ferguson


Simon (PJ) sez:
> Is this a storm in a teacup? Much huff and puff for a seldom-occurring
> situation?  No!  It happens to me ALL THE TIME.

I have to join Simon out of the closet, and confess that I write
Clunky Functions rather a lot too, or at least find myself going to
significant lengths to avoid them.  (No coincidence that the first
ghc-2.02 bug I noticed was that "maybe" was missing...)

Syntax:  I think what Simon proposes is reasonable, though I have minor
reservations about the use of "<-".  The monadic rationale seems a bit
thin, but will do in a pinch.  Simon's examples alternate between using
comma-separation, and layout separation:  I assume the latter is a
Freudian typo, but might be a viable alternative.

Heribert Schutz's suggestions I'm more wary of; I can't immediately
think of any example which would require syntax this general, and it's
also hard to come up with a more readable alternative.  I can see
the attraction of turning pattern-guards into an actual monad, Maybe
or otherwise, but I think it'd require some sugaring of the unit case,
which is after all what will be written 99% of the time, reviving
the issue of what syntax to use for it.  The example using this
syntax, in fact, doesn't make essential use of pattern guards at all,
so I'm as yet agnostic about how much it buys.

Slainte,
Alex.
--

> -- version 5a
> simplify (Plus e e') = fromJust ( [s' | Val 0 <- Just s ]
>++ [s  | Val 0 <- Just s']
>++ Just (Plus s s') )
>where
>s  = simplify e
>s' = simplify e'
> simplify e   = e






Re: A new view of guards

1997-04-29 Thread Johannes Waldmann

simonpj's proposal on guards:

> > I would really welcome feedback on this proposal.  Have you encountered
> > situations in which pattern guards would be useful?  Can you think of ways
> > in which they might be harmful, or in which their semantics is non-obvious?
> > Are there ways in which the proposal could be improved?  And so on.

M. Chakravarty:

> ... The proposed syntax may look a bit strange in the beginning,
> but I find the upward compatibility and the simple changes to the
> grammar very attractive.

after some thought, the syntax looks just right for me. after all,
the proposal could be read as transforming

fun x | Just b <- ..., more guards = expression

into

fun x = do { Just b <- ..., more guards, return expression }

which makes sense since this is really happening in the
underlying (identity) monad. 

in fact it's not the identity but it
also has a zero (pattern doesn't match) 
and a (++) (if left arg. fails, try right arg.)
as in 

fun x | guardx = ...; fun y | guardy = ...

which "really" is

fun =  (\ x -> do { guardx, return ...} ) 
++ (\ y -> do { guardy, return ...} ) 


-- 
Johannes Waldmann   Institut für Informatik   FSU   D-07740  Jena  Germany
http://www5.informatik.uni-jena.de/~joe/ mailto:[EMAIL PROTECTED]