Alex Ferguson writes:
> Heribert Schuetz:
> 
> > 3. From Alex' example (version 5a) one could have learned that we do not
> >    need guards at all, [...]
> 
> I don't know if Heribert suggests this in earnest, or as a reductio
> ad absurdum of my suggestion, [...]

Closer to the latter, but only for your argument that version 5 doesn't
make "essential use" of pattern guards at all. I wanted to point out
that no use of patterns is really "essential" (see also the equivalences
below), or at least that it is a bit arbitrary what one considers
essential.

> [...]
> The syntax here isn't clunky, I'll give you that, but if one wanted
> to pattern-guard with anything other than a Maybe (and Simon produced
> a couple of such examples), then things would start to look rather
> awkward again.

I somehow agree with that:

  data FooBar = Foo Int | Bar Float | Baz String

  f :: ... -> FooBar

  g x | Foo i <- f x = ...
      | Bar y <- f x = ...
      | Baz s <- f x = ...

looks nicer than

  g x | Foo i <- Just (f x) = ...
      | Bar y <- Just (f x) = ...
      | Baz s <- Just (f x) = ...

but here I anyway think that Philip Wadler's scepticism about an
optimizer factoring out the RHSs of the qualifiers may be justified.
Furthermore one might very well argue that for this example one should
use good old "case":

  g x = case f x of
          Foo i -> ...
          Bar y -> ...
          Baz s -> ...

Simon's example

  f x | [y] <- x,
        y > 3,
        Just z <- h y
      = ...

is charming, but probably requires repetition of guard prefixes as soon
as you want to define f for other arguments. I guess that it was not a
pure coincidence that the "clunky" example was based on Maybe. (Ok,
"simplify" was a non-Maybe example.) But where can I get Simon's
examples that you mentioned?

> >    - It does not need the explananation of a new semantics for "<-" with
> >      a non-monadic expression on the RHS.
> 
> I don't see this as a real advantage.  It just changes the rationale
> from one restricted monadic case (a mutated version of Id), to an
> equally restricted version on another Monad, neither of which is
> truly consistent with both the other uses of "<-", which take arbitrary
> monads.  Not that either upsets me greatly, just that I don't see it
> as arguing for one over the other.

Yes, it does simply replace one restricted case by another one. Like
you, I don't find the restriction to a fixed type that awful. (We have a
similar restriction to Bool in guards now, simply because it makes
sense.) But I still think Maybe is appropriate while Id is not:

- In the Id case it is a mutated version of the Monad, as you said.
  Haskell syntax does not support the identity monad, and also the
  semantics is not really the one of an identity monad, because the
  latter cannot fail (i.e., is not a MonadZero).

- "Maybe qualifiers" in guards are fully consistent with qualifiers in
  monad comprehensions: An equation

    f pats | quals = expr

  is equivalent to

    f pats | vars <- [vars | quals] = expr

  where vars is the tuple of variables bound by quals.  Furthermore a
  function definition

    f pat_11 ... pat_1k | quals_11 = expr_11
                        ...
                        | quals_1m = expr_1m
    ...
    f pat_l1 ... pat_lk | quals_l1 = expr_l1
                        ...
                        | quals_ln = expr_ln

  is equivalent to

    f v1 ... vk = fromJust ([out | pat_11 <- Just v1,
                                   ...
                                   pat_1k <- Just vk,
                                   out <- [expr_11 | quals_11] ++
                                          ... ++
                                          [expr_1m | quals_1m]]
                            ... ++
                            [out | pat_l1 <- Just v1,
                                   ...
                                   pat_lk <- Just vk,
                                   out <- [expr_l1 | quals_l1] ++
                                          ... ++
                                          [expr_ln | quals_ln]])

  where v1 ... vk are new variables.

  Note that in these equivalences the qualifiers need absolutely no
  syntactic adaption.

  Do similar equivalences hold for the identity approach? Does the
  identity approach require/provide an extension of the Haskell Kernel?


I also thought a bit about generalizing to arbitrary monads, but I think
it does not work (at least not in a straight-forward way).  The reason
is that something like "fromJust" exists for Maybe and Identity, but not
for arbitrary monads.  The suggestion that

 f g xs | x <- xs = g x

should define f to be equivalent to "map" is not compatible with the
above approach nor with Simon's because it only allows to define
functions of monadic types.  Furthermore it is not backward compatible
since

  f xs | False = xs

currently means that "f [1, 2, 3]" is undefined whereas with the
generalized monadic approach "f [1, 2, 3]" would be the empty list.
(Did I get this right?)

- ----------------------------------------------------------------------

Ok, this was a long message again. Hopefully it was not too boring.

Heribert.



Reply via email to