Replacing and improving pattern guards with PMC syntax

apfelmus at quantentunnel.de apfelmus at quantentunnel.de
Tue Oct 3 11:03:56 EDT 2006


> The
> problem is not that there is syntactic sugar for pattern matching,
> but that this isn't sugar coating at all - there is functionality hidden
> in there that cannot be provided by the remainder of the language.
> 
> In other words, pattern matching and associated "sugar" become
> part of Haskell's core, which thus becomes more complex,
> without offering sufficient compensation in terms of expressiveness.

I agree. The pattern matching problem is best solved by supplying sugar
which either is compositional or fundamental.

The compositional structure behind pattern guards is of course
(MonadPlus Maybe). So an idea could be to give the plus in MonadPlus
suitable syntactic sugar (which it currently lacks) and get pattern
guards for free. This can be too much, but at least there might be some
kind of sugar for the specific (MonadPlus Maybe) which actually yields
pattern guards.

I think of sugar along the lines of the following example

f (Right (Right p)) = p
f (Left p)          = p
f p                 = p

and its sugared version

f p = fromJust $
    | Right q <= p
        | Right r <= q  = r
    | Left q <= p       = q
    |                   = p

where the nested pattern is split in two parts for purpose of
demonstration. I don't know whether this can be parsed, but it's
intended to be parenthesized as follows:

{| {Right q <= p; {| { Right r <= q; = r;}}; };
{| {Left q <= p; = q;}};
{| {= p;}};

The intention is that | behaves like do with the extra feature that
adjacent | are collected together by `mplus`. So the desugaring of a
list of | statements is like

    data | a = | a
    desugarBar :: [| (Maybe a)] -> Maybe a
    desugarBar xs = foldr1 mplus [expr | {| expr} <- xs ]

Further,

   pat <= expr

is equivalent to

   pat <- return (expr)

and that's why we add <= different from <-. Note that <= is not
equivalent to {let pat = expr;} and this is actually the whole point of
the story.

The {= p;} should of course desugar to {return p;} and can somehow end a
| scope. It might be difficult to parse but looks much better than return p.


Inside the |, things are like in do notation. This means that the
delimiter is (;) and not (,) and we have full (<-) access to monadic
actions of type (Maybe a):

    | Right q <= p; Right r <= q   = r
<==>
    do
        Right q <- return p
        Right r <- return q
        return r

    | val <- lookup key xs; val2 <- lookup key2 xs; = val1+val2
<==>
    do
        val  <- lookup key xs
        val2 <- lookup key2 xs
        return (val1 + val2)


It's possible to nest | as we all know it from do

    | Right q <= p;
	{| Left r <= p   = r
         | Right r <= p  = r
        }

with curly braces added only for clarity. Layout should eliminate them.
Note how this works nicely with the fact the the last statement in do
notation implicitly determines the returned value.

Another thing to consider are boolean guards which could be
automatically enclosed by a corresponding (guard):

    | Right q <= p; p > 5;    = p-5
<==>
    do
        Right q <- return p
        guard (p > 5)
        return (p-5)


One last thing is to eliminate fromJust:

    f x
        | (interesting things here)

should be syntactic sugar for

    f x = fromJust $
        | (interesting things here)



Regards,
apfelmus



More information about the Haskell-prime mailing list