[Haskell-cafe] Pattern combinators

David Menendez dave at zednenem.com
Sun Dec 21 00:37:40 EST 2008


On Sat, Dec 20, 2008 at 9:34 PM, Jacques Carette <carette at mcmaster.ca> wrote:
> Andrew Wagner wrote:
>>
>> Wadler posted a blog entry the other day about a paper on pattern-matching
>> in Haskell (http://wadler.blogspot.com/). I've taken a first stab at turning
>> it into actual code for hackage (http://hpaste.org/13215). There are two
>> commented-out definitions that don't type-check, though, and the types are
>> too wild for me to grok. Anybody have any suggestions for 1.) How to fix it
>> and/or 2.) How to use data/type/newtype to simplify the types and make it
>> more manageable? Thanks!
>
> Both errors are because you are using "any" instead of "any'"; you might
> wish to put
> import Prelude hiding any
> at the top of your code, just to avoid such confusion.

Example 14 also uses (.->.) where it should use (.>.), and it either
needs some more parentheses or some precedence declarations for the
operators.

> To make the types more readable (but not necessarily more manageable), I
> have made some changes to my version of this code.

One oddity in the paper is the type of the failure continuations, ()
-> ans. I'm guessing that's left over from an earlier phase of
development. In my own transcription of the library, I eliminated the
() parameter without apparent loss of functionality.

I think I've managed to work out the structure of the types, which can
mostly be expressed in modern Haskell.

The matching part of the patterns have this general form:

    type PMatch vec vec' ans = (vec -> ans) -> (() -> ans) -> vec' -> ans

where vec and vec' are the list of argument types before and after the
subpattern match, and ans is the final answer. (In my code, I just use
ans instead of () -> ans for the failure continuation.)

This gets us:

nil   :: PMatch vec vec ans
one   :: a -> PMatch (a,vec) vec ans
(#)   :: PMatch vec vec' ans -> PMatch vec' vec'' ans -> PMatch vec vec'' ans
fail  :: PMatch vec vec' ans
catch :: PMatch vec vec' ans -> PMatch vec vec' ans -> PMatch vec vec' ans

These types are less general than the ones Haskell would infer, but
they do not appear to lose any functionality.

The currying part of the pattern is less easy to analyze. I've been
able to use type families to relate the curried and uncurried form of
the function types, but I'm working with GHC 6.8, so it's possible
this won't work with the more modern implementations.

Given the list of argument types and the answer type, generate a
curried function type:

    type family Curry vec ans
    type instance Curry () ans = ans
    type instance Curry (a,vec) ans = a -> Curry vec ans

zero, succ zero, and so forth take a function in curried form and
transform it into a function that takes a nested tuple:

    type CurryDigit vec ans = Curry vec ans -> vec -> ans

    zero :: CurryDigit () ans
    succ zero :: CurryDigit (a,()) ans

    succ :: CurryDigit vec ans -> CurryDigit (a,vec) ans
    succ . succ :: CurryDigit vec ans -> CurryDigit (a,(b,vec)) ans

So the currying part of the pattern will have the form:

    type PCurry vec vec' ans = CurryDigit vec' ans -> CurryDigit vec ans

So a pattern has the type,

    type Pattern a vec vec' ans = (PCurry vec vec' ans, a -> PMatch
vec vec' ans)

where a is the value being examined, vec and vec' are the list of
unbound argument types before and after the match, and ans is the
result.

    var :: Pattern a (a,vec) vec ans
    cst :: (Eq a) => a -> Pattern a vec vec ans
    pair :: Pattern a vec vec' ans -> Pattern b vec' vec'' ans ->
Pattern (a,b) vec vec'' ans


Coming from the other side, match takes a value and a case statement
and produces a result:

    type Case a ans = a -> (() -> ans) -> ans   -- or just a -> ans ->
ans in my code

    match :: a -> Case a ans -> ans

(|||) combines case statements:

    (|||) :: Case a ans -> Case a ans -> Case a ans

and (->>) creates them from a pattern and a curried function,

    (->>) :: Pattern a vec () ans -> Curry vec ans -> Case a ans

Note that (->>) requires the pattern to leave no unbound variables
after matching.


Given the way everything is polymorphic in ans, it may be possible to
hide it, but I haven't tried yet.


> The principal weakness of these pattern-matching combinators is that there
> is no support for algebraic types, i.e. things like
> data Tree a = Leaf | Branch (Tree a) (Tree a)
> I can see how to use Typeable to deal with that, but is there a simpler way?

You can define the patterns manually:

leaf = (id, \v -> case v of { Leaf -> nil; _ -> fail })

branch p q = (curry_p . curry_q, \v -> case v of { Branch l r ->
match_p l # match_q r; _ -> fail})
    where
    (curry_p, match_p) = p
    (curry_q, match_q) = q

I assume generating these would be pretty straightforward to automate
with Template Haskell.

-- 
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list