Simon L Peyton Jones writes:
> The discussion about pattern guards has raised two interesting and 
> (I think) independent questions:

I think these questions are independent to some degree, but not entirely
unrelated. I have written a few sentences on this in an earlier message,
but perhaps the considerations below about the number of
(information-carrying) constructors of a type help to clarify this.

>       - Nested guards

I have no strong opinion on that. The only thing I want to note here:
If someone finds a nice syntax for nested guards and this should be
introduced into the language, then for the sake of uniformity this
syntax should also be considered for monad comprehensions and "do"
expressions.

[Perhaps "case" can be introduced into the syntax of monad
comprehensions and "do" expressions in a way similar to "let".]

>       - Maybes and monads

> * 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 admit that this has not been clear to me when I suggested use of Maybe
for the first time. It has only become clear to me later during the
discussion with Alex Ferguson.

So I agree with you that expressivity is not an argument for either
proposal. And of course all the other arguments I can find are then in a
way just a matter of taste.

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

At first sight, this example looks convincing. But extending your
argumentation one might argue that in Maybe comprehensions we should
write

  [... | ..., Just (y:ys) <- h x, ...]

rather than

  [... | ..., (y:ys) <- h x, ...]

because the former would make all the pattern matching explicit.
However, we can live well with the implicit matching here.

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

I'm afraid this example suffers from the same problem as my "simplify"
example did: It does not perform a test and can thus be replaced by

  f c = ...
    where (i,j) = toRect c

or by

  f c = let (i,j) = toRect c in ...

assuming the definition of toRect without Maybe, of course. Probably the
example can be repaired so that it "needs" the new guards, but then it
would also look more contrived.

> * Heribert's main motivation was that Maybe is a monad with a zero.

... and also that Maybe is "the prototype" of a type with two
constructors one of which is information-carrying. Why is this a
motivation? Here are the reasons:

- As you said in your very first message on this topic, pattern guards
  become clunky again if a type has more than one information-carrying
  constructor.

- Furthermore, a type with more than two constructors (even if only one
  is information-carrying) is not really suited to pattern guards,
  except if we consider just one constructor special and want to handle
  all the others with the same RHS. (This was the case in the "simplify"
  example, which can therefore be seen as an argument in favour of your
  suggestion.)

  Typically, however, I would expect "case" or nested guards to be the
  most appropriate constructs for types with more than two constructors
  or more than one information-carrying constructor.

- Finally, for a type with a single constructor we don't need pattern
  guards at all, since for such types matching can be done in a "where"
  clause. (The exception is if this sort of matching appears between two
  qualifiers that may fail.)

If one does not find this a compelling argument for Maybe but for a
larger class of types, as Alex Ferguson suggested, then we might come
back to the MonadChoice class.

>   Well that's often a good motivation, but I don't buy it here.  What
>   benefit does it actually provide to the programmer?

Perhaps nothing to the experienced programmer, but something (namely
more uniform language semantics) to the novice that learns about pattern
guards and monad comprehensions.

Furthermore, Maybe is somehow the most "natural" type to use here (Yes,
this is a matter of taste.), which also occurs frequently. (But as I
said in an earlier message, the frequency of Maybe is not the most
important argument to me.)

> The length and complexity of Heribert's general-monads
> message is a bit daunting.  I'm not convinced!

I agree that the length of the general-monads example doesn't make it
too convincing: Just one occurrence of the language feature in question
in a long program...

Perhaps the following (shorter but less detailed) example helps to
convince you (or somebody else):

  Constraint solvers would be typical members of MonadChoice: Qualifiers
  add constraints to a constraint store and the monad becomes zero when
  the set of constraints becomes unsatisfiable. We may consider
  alternative insertions (++) and we may extract the constraint store in
  the case of success (choice).

  Now consider a function f that should do one thing if a constraint c
  is compatible with a constraint set cs and another thing otherwise:

    f :: (Constraint a) => [a] -> a -> ...
    f cs c | () <- initConstraints cs,
             () <- addConstraint c     = e1
           | otherwise                 = e2

  A nice property is that f can be used for arbitrary constraint types.

  You might, e.g., suggest the output type Bool for addConstraint,
  saying whether the insertion worked, and replace the second qualifier
  above with

             True <- addConstraint c

  or simply

             addConstraint c

  which works with your semantics. But then one would have to write the
  different and more obscure qualifier
  
             True <- return (addConstraint c)

  in a comprehension for the constraint solver monad.


Some more notes on the MonadChoice approach:

- I don't know whether I should prefer the Maybe approach to the
  MonadChoice approach or vice versa, but I prefer these two to the
  non-Maybe approach.

- The Maybe approach can be extended to MonadChoice or the like in a
  second step if this is considered useful at some later time. For the
  non-Maybe approach I think this is not possible. (But perhaps you say
  it is not needed either.)

- Warren Burton's concern about the MonadChoice approach was that it would
  lead to obscure error messages. These messages might be similar to the
  one produced by

    y = [x | let x = "foo"]

  (BTW: I don't know why "y :: Monad a => a String" isn't derived here
  automatically, but this is a different issue.)
  And it becomes really ambiguous with

    z = choice "bar" [x | let x = "foo"]

  But couldn't default declarations (as Haskell provides them for numeric
  types) work here too?


Meanwhile I understand your point of view better than I used to, but
still I'm not willing to give up mine. Since it looks like it is to a
large extent a matter of taste whether Maybe should be used in guards or
not, perhaps the entire question is not that important.

Heribert.



PS: In my last Mail the standard library function "fromMaybe" can be
used to simplify the definitions of "choice" in the instance declaration
for Maybe and "choice'" for MonadToMaybe as follows:

53c53
<   choice d m = maybe d id m
---
>   choice = fromMaybe
252,254c252
< choice' d m = case toMaybe m of
<                 Nothing -> d
<                 Just x  -> x
---
> choice' d m = fromMaybe d (toMaybe m)



Reply via email to