The discussion about pattern guards has raised two interesting and 
(I think) independent questions:

        - Nested guards
        - Maybes and monads

Here are my thoughts on these things, typed 30,000 feet above Utah!

Simon


Nested guards
~~~~~~~~~~~~~~
Several people have pointed out that one might want to 
nest guards.  For example, in Haskell we can say

  f (x:xs) | x<0 = e1
           | x>0 = e2
           | otherwise = e3

But now suppose that the pattern (x:xs) was the result of
an auxiliary call to h.  Trying to use pattern guards (as I proposed them)
we might say:

  g a | (x:xs) <- h a, x<0 = e1
      | (x:xs) <- h a, x>0 = e1
      | otherwise = e3

Here we repeat the call to the auxiliary function, h, in the
two guards, which is 
        (a) a nuisance, and 
        (b) an efficiency worry, because h might be expensive.

In this case (and in fact, I believe,
in most cases) we can deal with (b) using a where clause:

  g a | (x:xs) <- h_a, x<0 = e1
      | (x:xs) <- h_a, x>0 = e1
      | otherwise = e3
      where
        h_a = h a

But (a) remains.  Furthermore, it isn't always possible to
use a where clause:

  g2 a | (x:xs) <- h a, (y:ys) <- h x, y<0 = e1
       | (x:xs) <- h a, (y:ys) <- h x, y>0 = e1
       | otherwise = e3

Here, we can't use a where clause to share the calls to (h x).

One might argue that a compiler should spot the common calls to
(h a) and (h x) and common them up.  Indeed I think I argued this
earlier, drawing the analogy with the way we expect a compiler to
avoid unnecessary pattern matching where possible.  But there's a BIG
difference between this and avoiding pattern-matching: pattern-matching
is a small constant cost, whereas making two calls to "h" instead of
one could conceivably have a dramatic effect on efficiency, or even 
change the complexity of the algorithm.  So I certainly agree that
the programmer should be able explicitly to share calls to "h".
In the case of "g" that's possible using a where clause.  In the
case of "g2" it is not.  To share the call (h x) in "g2" we are
pretty much reduced to the clunkiness I objected to in my initial
proposal.  This is a definite shortcoming of my proposal, though
I would like to argue that really bad cases seldom occur.  For
example, in this case we could write (rather less elegantly)

  g2 a | (x:xs) <- h a, (y:ys) <- h x = if y<0 then e1
                                        else if y>0 then e2
                                        else e3


To avoid this difficulty with functions like g2,
Heribert Schuetz suggests having nested guards, something
like this:

  g a | (x:xs) <- h a
          | x<0 = e1
          | x>0 = e2
          | otherwise = e3

The second column of "|" guards is nested inside the first
guard, so that if one of the inner guards fail we simply try
the next without backtracking to the top-level guard.  He points
out, quite correctly, that Haskell already allows a form of nested
choice by having a set of guards for a single set of patterns
and associated where clause.

Haskell doesn't currently allow nesting within pattern matches
either.  In the equations

        f (x1:x2:xs) []     = e1
        f (x1:x2:xs) (y:ys) = e2

one has to write out the pattern (x1:x2:xs) twice, even though what
we have in mind is presumably to match the pattern (x1:x2:xs) first,
and then choose among the right hand sides based on the second argument.
Phil Wadler suggests that we might want to revisit that choice too.

These are all good points.  Nested choices are somewhat natural (although
they run counter to the general idea of independent equations), but Haskell
permits only a certain particular sort of nested choice (patterns, then
muultiple guarded RHSs).  It would be nice to find a syntax that neatly
incorporated nested choice at any level, among patterns or among guards
(indeed we can see patterns as a particular sort of guard).  Nevertheless,
this would be a more far-reaching proposal.  My proposal is a modest one:
it aims to deal with a large number of commonly occurring and very irritating
cases.  There remain cases (such as g2 above) that it does not handle well.
But, given the smallness of the change required, I think it's a good deal.



Maybes and monads
~~~~~~~~~~~~~~~~~~
Heribert also suggests that the typing rule for a
pattern guard "p <- e" should have p::t, e::Maybe t.
Thus

        f :: Int -> Int
        f x | (y:ys) <- h x = e1
            | otherwise     = e2

        h :: Int -> Maybe [Int]
        h x = ...

Here, the guard would fail either if h returns Nothing, or
if it returns (Just []).

I must say that I don't find this convincing:

* The e::Maybe t proposal is equivalent in expressive power
  to mine (e::t).  Each can express precisely the programs
  that the other can, by adding a few "Justs".

* I positively like that with e::t I would write

        f x | Just (y:ys) <- h x = e1
            | otherwise          = e2

  This is a bit longer than e::Maybe t, but it does mean that
  all the pattern matching is explicit, not just part of it.

* Using e::Maybe t would make using pattern guards for views
  much clunkier.  Suppose I have a rectangular and polar view
  of complex numbers:

        toRect :: Complex -> (Float,Float)
        toPolar :: Complex -> (Float,Float)

  To use them I would have to write

        f c | (i,j) <- Just (toRect c) = ...

  If I do a lot of "toRect" calls this could be a real pain. So
  I might choose instead to change toRect:

        toRect :: Complex -> Maybe (Float,Float)

  But not toRect's type suggests that it might fail, which is not
  the case; and it would now be dreadful to use in a let or case
  expression:

        case toRect c of Just (x,y) -> ...

  Or perhaps I'd have two versions of toRect.   But all of this seems
  like an unwelcome distraction.  e::t seems much more straightforward.

* Heribert's main motivation was that Maybe is a monad with a zero.
  Well that's often a good motivation, but I don't buy it here.  What
  benefit does it actually provide to the programmer?


One answer to the last question might be "none, until we generalise to
arbitrary monads".  Heribert did exactly this, in a long and
well-written message.  Functional programmers love generalising
things, but I think we need a more clearly-demonstrated need before
doing so. The length and complexity of Heribert's general-monads
message is a bit daunting.  I'm not convinced!



Reply via email to