[Haskell-cafe] Re: [Haskell] Replacing and improving pattern guards with PMC syntax

Brandon Moore brandonm at yahoo-inc.com
Mon Oct 2 03:10:59 EDT 2006


kahl at cas.mcmaster.ca wrote:

...

> So far I never considered it important to devise a concrete syntax for PMC,
> but triggered by the current pattern guards thread on haskell-prime,
> I now try to give a PMC syntax that blends well with Haskell.

I think with some alterations your syntax would blend even better. In
particular, it would be really nice to have a backwards-compatible 
syntax. I have designed a slightly different syntax with that goal in 
mind, which is described in the rest of this message.

> One of my gripes with Haskell pattern matching is
> that the anonymous variant, namely case expressions,
> has an application to an argument built in,
> and therefore does not by itself produce a function.
>
> However, lambda-abstraction already allows single-alternativepattern matching, so I propose to relax this to multi-alternative
> pattern matching:
>> length = \
>>   [] -> 0
>>   x : xs -> 1 + length xs
I'm with you here. Extending lambda to introduce a layout group of
alternatives makes sense even without the rest of the changes to
matching. This isn't completely backwards-compatible, but it's pretty close.

While we're at it, why not have the identifier of a top level definition
introduce a layout group of alternatives, rather than requiring the name
to be repeated all the time.
How about

take
0 _ = []
_ [] = []
n (x:xs) = x : take (pred n) ns

> (Lists of alternatives correspond to the ``matchings'' of PMC,
>  and concatenation of those lists (using ``;'' or layout) corresponds
>  to matching alternative in PMC.
>  ``\ m'' then corresponds to ``{| m |}'' in PMC.
> )
>
> For multi-argument pattern matching,
> I propose to allow nested matchings:
>> zip = \
>>   x : xs -> y : ys -> (x,y) : zip xs ys
>>   _      -> _      -> []
This deviates from the current syntax of multi-argument lambda, and
introduces overloading on ->. Perhaps -> could be reserved for "match
and lift", and whitespace could separate several alternatives:

zip = \
(x:xs) (y:ys) -> (x,y) : zip xs ys
_ _ -> []

There is some tension in the current between argument lists which allow
several arguments and require parentheses around constructor
applications to delimit patterns, and case expression which match only
one item, but without grouping.

If we are trying to unify things, perhaps case could be extended to
support matching several values together, perhaps separating expressions
with commas in the head and using the syntax of a lambda for the cases.

Perhaps '=' in function declarations vs. "->" for other matching could
also be simplified somehow. I don't have any ideas here.

>> take' = \
>>   0 ->   _      -> []
>>   n -> { []     -> []
>>        ; x : xs -> x : take (pred n) xs
>>        }
I'm not sure how to handle a case like this. Introducing layout at
whitespace seems a bit excessive, but requiring explicit separators
looks a bit heavy on punctuation next to the current grammar, where only
records (and perhaps
Maybe the '\' could be reiterated to introduce the layout group:

take' = \
0 _ -> []
n \[] -> []
(x:x) -> x : take (pred n) xs

>
> Pattern guards now can be seen as a special case of
> alternatives-level argument application
> (``argument supply'' $\righttriangle$ in PMC).
> I find it useful to write the argument first, as in PMC.
>
> I see two options of writing argument supply in Haskell:
> either using new keywords, giving rise to the syntax production
>
> alt -> match exp with alts
Maybe reuse "case", unless a new keyword is needed to avoid confusion.
> or using a keyword infix operator:
>
> alt -> exp |> alts
>
> (Using this kind of argument supply instead of pattern guards
>  also has the advantage that multiple alternatives become possible.)

I'm not using -> to separate patterns, but some leading symbol is
required to separate the last pattern from the expression.

I like '|' from the current syntax, selected with hopes of incorporating
and extending the current guard syntax.

I'm pretty sure incorporating the existing guard syntax will require
that the grammar keep track whether the last "bit" of the matching was a
pattern or a guard (just like currently | switches from patterns
separated by whitespace to a list of guards separated by commas).

Pattern guards can be translated to matching plus argument supply, so
argument supply needs to be part of the primitive matching syntax. I
like the suggestion
alt | exp |> alts
It would be unambiguous but require unbounded lookahead to allow a case
to begin with argument supply:
foo :: [Int] -> [Int]
foo = \lookup env v |> (Just r) [] -> [r]

Given argument supply, we can sugar in the existing guard syntax by allowing
alt | guard, guards, exp |> alts
and
alt | guards -> expr

The sequence "->\" will transition from guards back to matching more
arguments. It might be nice to abbreviate that to '\'.

Guards can be eliminated with the translations

alt | exp, guards ...
==>
alt | exp |> True |guards

alt | exp -> expr
==>
alt | exp |> True -> expr

alt | pat <- exp, guards
==>
alt | exp |> {pat | guards ... }

alt | pat <- exp -> expr
==>
alt | exp |> pat -> expr

>
> I start with Simon Peyton Jones' standard example:
>
>> clunky env v1 v2 |  Just r1 <- lookup env v1
>>                   , Just r2 <- lookup env v2  = r1 + r2
>>                  | otherwise                  = v1 + v2
I'd like to accepts this unchanged. I think the treatment of guards
above will work.
> This could now be written using either ``match _ with _'':
>
>> clunky env v1 v2 = \
>>   match lookup env v1 with
>>     Just r1 ->  match lookup env v2 with
>>       Just r2 ->  r1 + r2
>>   v1 + v2
>
> or infix ``_ |> _'':
>
>> clunky env v1 v2 = \
>>   lookup env v1   |> Just r1 ->
>>     lookup env v2 |> Just r2 ->  r1 + r2
>>   v1 + v2
Because I'm using space to separate patterns, I would require
parentheses (or the pat <- exp sugar)

clunky env v1 v2
| lookup env v1 |> (Just r1)
, lookup env v2 |> (Just r2) -> r1 + r2

> Boolean guards are matches against True:
>> take = \
>>   0 ->   _      -> []
>>   n -> match n > 0 with
>>      True ->
>>        { []     -> []
>>        ; x : xs -> x : take (pred n) xs
>>        }
>>      _ -> error "take: negative argument"

take = \
0 _ -> []
n | n > 0 \[] -> []
(x:xs) -> x : take (pred n) ns

This syntax has a pretty nice pronunciation,
reading | as "such that", a comma as an "and" (between guards), and both
space between patterns or '\' after a guard as
"and" or "and then" (either way, introducing a pattern for another
argument).

This PMC stuff seems like a description/semantics for pattern matching.
Hopefully my attempts at backwards-compatible syntax help people give
the semantics a deeper look.

Brandon



More information about the Haskell-Cafe mailing list