
All, 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!

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.
To make the types more readable (but not necessarily more manageable), I have made some changes to my version of this code. For example, instead of () as the "empty stack", I use data Void void = undefined :: Void in the definition of 'zero' (and thus also in p .>. k). I also use data FUnit = FUnit -- Unit just for fail Lastly, instead of having a matcher be a pair (which obscures the use of pairs as a stack in other places, as well as matching on pairs), I defined data Matcher a b = Matcher a b and use that everywhere. This all makes the types larger to type, but at least there is a cleaner separation of concerns, which makes the errors easier to figure out. 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? Jacques

On Sat, Dec 20, 2008 at 9:34 PM, Jacques Carette
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

I'd love to see a copy of this go up on hackage for experimentation. Would
you care to upload your code, or send it to me so I can upload it?
On Sun, Dec 21, 2008 at 12:37 AM, David Menendez
Andrew Wagner wrote:
Wadler posted a blog entry the other day about a paper on
On Sat, Dec 20, 2008 at 9:34 PM, Jacques Carette
wrote: 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
<http://www.eyrie.org/~zednenem/ http://www.eyrie.org/%7Ezednenem/>

On Sun, Dec 21, 2008 at 10:14 PM, Andrew Wagner
I'd love to see a copy of this go up on hackage for experimentation. Would you care to upload your code, or send it to me so I can upload it?
I've uploaded my latest version to http://hpaste.org/13263. It
explicitly makes patterns polymorphic over the answer type of the case
statement by making Pattern a newtype and universally quantifying the
(un)currying and matching functions.
For example,
(->>) :: Pattern a () vec -> Curry vec ans -> Case a ans
I'm not sure it makes sense to create a package just yet. At the very
least, you should ask Morten Rhiger first. The type signatures are
mine, but the code is mostly straight transcriptions from his paper.
--
Dave Menendez

David Menendez
On Sun, Dec 21, 2008 at 10:14 PM, Andrew Wagner
wrote: I'd love to see a copy of this go up on hackage for experimentation. Would you care to upload your code, or send it to me so I can upload it?
I've uploaded my latest version to http://hpaste.org/13263. It explicitly makes patterns polymorphic over the answer type of the case statement by making Pattern a newtype and universally quantifying the (un)currying and matching functions.
For example,
(->>) :: Pattern a () vec -> Curry vec ans -> Case a ans
I'm not sure it makes sense to create a package just yet. At the very least, you should ask Morten Rhiger first. The type signatures are mine, but the code is mostly straight transcriptions from his paper.
Hi, I've tried to undestand the paper, in particular the relation between the combinators written in cps style and combinators written using a Maybe type (i.e pattern matching functions returning Maybe to signal success or failure). The code below gives an implementation of the basic pattern matching functions on top of two possible implementation of an abstract interface for building and using bindings. In particular using type families it seems to be possible to automatically construct a function inj to convert between a function in the form a->b->c->d to a function in the form (a,(b,c,())) -> d, thereby removing the need of building such coverter via the pattern matching functions like suggested in the paper. Since I'm an Haskell begineer I would appreciate very much comments or suggestions for improvements. Best, Massimiliano Gubinelli Here the code: ----------------------------------- {-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleInstances, RankNTypes #-} module PM where -- inj converts a function of the form a -> b -> c -> d to the -- uniform representation (a,(b,(c,()))) -> d class Fn a c where type Fnq a c inj :: Fnq a c -> a -> c instance Fn () c where type Fnq () c = c inj f () = f instance Fn b c => Fn (a,b) c where type Fnq (a,b) c = a -> Fnq b c inj f (a,b) = inj (f a) b -- pattern matching, cps style -- a binding function has three inputs: ks kf v. v is a list of -- current bindings. newtype PatA a b = PatA { unPatA :: forall ans. (b -> ans) -> ans -> a -> ans } applyA :: PatA a b -> (b -> c) -> c -> a -> c applyA (PatA p) ks kf v = p ks kf v meetA :: PatA a b -> PatA b c -> PatA a c meetA (PatA a) (PatA b) = PatA $ \ ks kf -> a (b ks kf) kf joinA :: PatA a b -> PatA a b -> PatA a b joinA (PatA a) (PatA b) = PatA $ \ ks kf v -> a ks (b ks kf v) v anyA :: PatA a a anyA = PatA $ \ ks kf -> ks noneA :: PatA a a noneA = PatA $ \ ks kf v -> kf varA :: x -> PatA a (x,a) varA x = PatA $ \ ks kf v -> ks (x,v) pairA a b (x,y) = meetA (a x) (b y) conA a x = if a == x then anyA else noneA andA a b x = meetA (a x) (b x) orA p n x = joinA (p x) (n x) matchA val pat = pat val () caseA a fa fb x v = applyA (a x) (inj fa) (fb x v) v otherwiseA kf = \x v -> kf isA p x = matchA x $ caseA p (\_ -> True) $ otherwiseA False testA1 z = matchA z $ caseA (conA (1,2)) ("first match") $ caseA (pairA (conA 1) varA) (\x -> "second match " ++ show x) $ caseA (pairA varA varA) (\x y -> "third match " ++ show x) $ otherwiseA "mismatch" -- pattern matching, Maybe style -- a binding function receives a list of current bindings and returns -- a Maybe type containing the list of updated bindings in case of -- success newtype PatB a b = PatB { unPatB :: a -> Maybe b } applyB :: PatB a b -> (b -> c) -> c -> a -> c applyB (PatB p) ks kf v = maybe kf ks (p v) meetB :: PatB a b -> PatB c a -> PatB c b meetB (PatB a) (PatB b) = PatB $ \v -> (b v) >>= a joinB :: PatB a b -> PatB a b -> PatB a b joinB (PatB a) (PatB b) = PatB $ \v -> maybe (b v) Just (a v) anyB :: PatB a a anyB = PatB $ \v -> Just v noneB :: PatB a a noneB = PatB $ \v -> Nothing varB :: x -> PatB a (x,a) varB x = PatB $ \v -> Just (x,v) pairB a b (x,y) = meetB (a x) (b y) conB a x = if a == x then anyB else noneB orB a b x = joinB (a x) (b x) andB a b x = meetB (a x) (b x) matchB val pat = pat val () --caseB a fa fb x v = maybe (fb x v) (inj fa) ((unPatB $ a x) v) caseB a fa fb x v = applyB (a x) (inj fa) (fb x v) v otherwiseB f = \x v -> f isB p x = matchB x $ caseB p (\_ -> True) $ otherwiseB False testB1 z = matchB z $ caseB (pairB (conB 1) (conB 2)) ("first match") $ caseB (pairB (conB 1) varB) (\x -> "second match " ++ show x) $ caseB (pairB varB varB) (\x y -> "third match " ++ show x) $ otherwiseB "mismatch"

On Sat, Jan 3, 2009 at 4:06 PM, Massimiliano Gubinelli
I've tried to undestand the paper, in particular the relation between the combinators written in cps style and combinators written using a Maybe type (i.e pattern matching functions returning Maybe to signal success or failure).
In your implementation, they are (almost) equivalent.
newtype PatA a b = PatA { unPatA :: forall ans. (b -> ans) -> ans -> a -> ans }
newtype PatB a b = PatB { unPatB :: a -> Maybe b }
Specifically, "PatA a b" is isomorphic to "a -> (forall ans. (b ->
ans) -> ans -> ans)" and "forall ans. (b -> ans) -> ans -> ans" is
(mostly) isomorphic to "Maybe b".
maybe :: Maybe b -> (b -> ans) -> ans -> ans
maybe (Just x) f z = f x
maybe Nothing f z = z
unMaybe :: (forall ans. (b -> ans) -> ans -> ans) -> Maybe b
unMaybe f = f Just Nothing
(As usual, seq prevents this from being a true isomorphism, because
maybe (unMaybe _|_) = const (const _|_), and seq allows us to
distinguish _|_ from const _|_.)
I'm not sure which form is preferable. I suspect the continuation
version will do less allocation, but with enough in-lining, GHC can
effectively convert the Maybe version into the continuation version on
its own.
--
Dave Menendez
participants (4)
-
Andrew Wagner
-
David Menendez
-
Jacques Carette
-
Massimiliano Gubinelli