[Template-haskell] The ':' operation with patterns ?
Alain Cremieux
alcremi@pobox.com
Sun, 26 Jan 2003 23:07:27 +0100
Hi,
I'm trying to code the exemples of "Template Meta-Programming" for
Haskell. Since there are differences in the implementation, I'm obliged
to understand what I code, which is a good exercise.
At present I'm stuck in the mkZip function, because I'm unable to create
a pattern which is a list concatenation of 2 patterns.
For expressions I can use 'listExp', but what is the equivalent for
patterns ?
the code :
-- call : $(zipN 3) as bs cs
zipN :: Int -> Expr
zipN n
| (n <= 0)
= fail "Incorrect arg to 'zipN' - zipN n, n >= 1"
| otherwise
= [| let zp = $(mkZip n [| zp |])
in zp |]
mkZip :: Int -> Expr -> Expr
mkZip n name = lam pYs (caseE (tup eYs) [m1, m2])
where
pXs, pYs, pXSs :: [Patt]
eXs, eYs, eXSs :: [Expr]
(pXs, eXs) = genPE "x" n -- x1, x2,...
(pYs, eYs) = genPE "y" n -- y1, y2,...
(pXSs, eXSs) = genPE "xs" n -- xs1, xs2,...
--pcons x xs = [p| $x : $xs |]
pcons :: Patt -> Patt -> Patt
pcons x xs = ptup (x : [xs]) -- NOT correct, gives (x, xs)
instead of x : xs
b :: Expr -- ((x1, x2,...) : (zp xs1 xs2 ...))
b = listExp [tup eXs, apps (name : eXSs)]
m1 :: Mtch -- ((x1:xs1), (x2:xs2),...) -> ((x1, x2,...) : (zp
xs1 xs2 ...))
m1 = alt (ptup (zipWith pcons pXs pXSs)) b
m2 :: Mtch -- (_, _,...) -> []
m2 = alt (ptup (replicate n pwild)) (listExp [])
-- alt = (a1, a2, ..., an) -> ai -- the match part of a case clause
(just an example)
alt :: Patt -> Expr -> Mtch
alt p e =
do x <- e
return (Mat p (Normal x) [])
Thanks,
Alain