I've marked the most interesting part of this mail with "#" signs below.
Alex Ferguson writes:
> Let me rephrase then; it wasn't a convincing example, because the
> non-pattern-guarding version (5a vs. 5) was actually simpler and
> cleaner, but in basically the same style.
Meanwhile it has become clear to me that "simplify" was too simple
originally. Here is the Maybe-style version with "someTest":
simplify (Plus e e') | someTest e e',
s <- Just (simplify e ),
s' <- Just (simplify e'),
result <- [s' | (Val 0) <- Just s ]
++
[s | (Val 0) <- Just s']
++
Just (Plus s s') = result
simplify e = e
If something like version 5a is still possible here, I can come up with
a yet more complex example ... but this leads away from the more
interesting aspects of the discussion.
> [...] perhaps it comes down to whether the Maybe case occurs
> "naturally" considerably more often than any others. If it does, then
> I'd be prepared to put up with having to write the occassional
> spurious-looking "Just".
Of course programming language design should take into account
possibilities for concisely expressing frequent cases. Nevertheless I
find it more important to avoid unnecessarily complex language
semantics. And, as you may guess, I find Maybe guards considerably less
complex than pseudo-Id guards.
> > (We have a similar restriction to Bool in guards now, simply because
> > it makes sense.)
>
> That's a very loose comparison; nothing in the syntax for guards
> hints that they _should_ have a more general interpretation, whereas
> "<-" does at least suggest monads (or a different particular monad,
> according to taste).
Nothing in the syntax of today's guards hints that they must be of type
Bool. Only the semantics of guards (defined by the translation to
if-then-else) requires this.
Similarly, nothing in the syntax of guard qualifiers hints that they
must be for the type Maybe. Only the semantics of guards (defined by the
equivalences in my last mail) requires this.
I find this a very close analogy.
# > > - 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).
# >
# > It may be that because the type can represent "failure", it's more
# > intuitive to use here, but I find this appeal to its "monadicness"
# > continues to be unconvincing.
#
# The immediate argument for monadicness is that qualifiers should be
# used consistently with their use in monad comprehensions.
#
# A deeper argument is the following: We have to decide whether we want
# to syntactically support a list of qualifiers or some sort of tree
# (remember my first mail). For the sake of conservativity and perhaps
# also for other reasons there seems to be some agreement on lists
# rather than trees (although Philip Wadler also contributed arguments
# in favour of the latter). And it is (part of) the essence of monads
# that operations on them can typically be handled in such a seqential
# way without branching. This is why "do" expressions and monad
# comprehensions have been introduced at all. (Yep, this is abductive
# rather than deductive argumentation, but this should be allowed here.)
#
# In other words: If you dont't want the restriction to monads, then
# I'll start again pleading for qualifier trees. (Is this a sufficient
# threat? ;-)
#
# > If it's really true that Maybe is the thing to use because it's a
# > Monad, MonadZero, and MonadPlus, why isn't it equally true of some
# > other M satisfying the same type constraint?
#
# Good point. But we also need something like "fromJust", i.e., a
# "canonical" function of type "M a -> a". Let's call it "extract". If
# this other M also supplies "extract", then it should work. So one
# might introduce a new constructor class for such monads and extend
# guard qualifiers from Maybe to this class. But we could also start
# with the simple Maybe-only case, which can be extended smoothly to a
# larger class of monads later.
#
# What do I mean by "canonical"? For the list monad a definition
# "extract = head" would be well-typed, but intuitively "head" is not
# canonical, because e.g. "last" could be used with the same right.
#
# Actually, I have found an example of a "monad with extract" that might
# be useful and is not isomorphic to Maybe. But it still requires some
# work, so I'll send it in another message.
> A more concise translation would be, for each clause of a function f:
>
> f as | pgs = e
>
> ==>
>
> f as | isJust m = fromJust m
> where m = [ e | pgs ]
Nice. I always forget that where-defined variables may already be used
in the guard. (This was also the reason for my too simple original
"simplify" example.)
An advantage of this translation is that it does not require a
MonadPlus, but only a MonadZero (+ "extract" + "isNotZero :: M a ->
Bool", i.e., something corresponding to isJust). Actually only a Monad
is required formally, but would isNotZero make sense in a Monad without
zero? (Perhaps defined as "isNotZero _ = True"???) Furthermore, boolean
expression qualifiers require a MonadZero.
A disadvantage is that this translation still uses boolean guards and we
need further handling of these. This is certainly possible, but is it
elegant?
> The non-Maybe pattern guards can be translated in the same way, with
> the additional step of doing, for each generator in pgs:
>
> p <- e
>
> ==>
>
> p <- Just e
This is exactly what I would prefer to avoid. It is possible to cope
with this, but for a Haskell beginner it is unnecessarily confusing to
have two different kinds of "<-" qualifiers. (It is hard enough to
understand that plain expressions mean completely different things in
"do" expressions and monad comprehensions. This should not be repeated
without a strong reason.)
> > Do similar equivalences hold for the identity approach? Does the
> > identity approach require/provide an extension of the Haskell Kernel?
>
> Note that Chris Dornan already gave a translation of pattern-guards into
> "core" Haskell.
That is, the Haskell kernel suffices, but the equivalences are not as
simple as in the Maybe case.
> Obviously, boolean guards need to be treated distinctly; as they're
> not a monadic type, I don't think the above translation is even possible,
> much less appropriate. If one wanted to unify the two, one could do
> the following:
>
> b ==> True <- b
>
> or
>
> b ==> True <- Just b
>
> according to preferred style of p-guard (non-Maybe or Maybe).
To me this would be even more horrible than the automatic insertion of
"Just" to the right of "<-" qualifiers. Note that it has been the charm
of Simon Peyton Jones' proposal that booleans in list comprehensions fit
directly with booleans in guards and that we get backward compatibility
without any tricks.
> It's a question of clarity, not expressivity.
I fully agree with that. But I must say I'm also afraid that the
language looses clarity if heterogeneous semantics is introduced just to
make code written in the language look a bit nicer superficially.
Heribert.