[Template-haskell] newbie question

Isaac Jones ijones@syntaxpolice.org
Tue, 08 Jul 2003 17:11:06 -0400


Greetings,

I'm new to Template Haskell and am trying to work out some examples.
I successfully used this function (makeSum n) to generate a function
that takes n arguments.

\begin{code}
-- |Given a size, n and n expressions, sum them up, so:
-- > $(makeSum 4) 1 2 3 10
-- => 16
-- > $(makeSum 4) 1.0 2.2 3.4 10.1
-- => 16.7

makeSum :: Int -> ExpQ
makeSum n = lam aPats (sumExps aVars)
    where
    -- create the symbols we'll need:
    aPats ::[Pat]
    aVars ::[ExpQ]
    (aPats,aVars) = genPE "num" n

    sumExps :: [ExpQ] -> ExpQ
    sumExps (h:t) = [| $h + $(sumExps t) |]
    sumExps []    = [| 0 |]
\end{code}

Now I would like to bring a bunch of versions of this function into
scope, something like

> $(genSummers 10)

where genSummers :: Int -> Q [Dec]
and brings into scope:

makeSum0 :: Int
...
makeSum2 :: Int -> Int -> Int
...
makeSum10 :: ...

So this seems to make sense:

> genSummers n = returnQ [Fun ("makeSum" ++ (show i)) [Clause [] (Normal $(makeSum i)) [] ] | i <- [1..n] ]

But actually, I run into a stage restriction.  Now I can create a function:

> makeSumE :: Int -> Exp

and say:

> genSummers n = returnQ [Fun ("makeSum" ++ (show i)) [Clause [] (Normal (makeSumE i)) [] ] | i <- [1..n] ]

But how to define makeSumE?  I try this:

\begin{code}
makeSumE :: Int -> Exp
makeSumE n = Lam aPats (sumExps aVars)
    where
    -- create the symbols we'll need:
    aPats ::[Pat]
    aVars ::[Exp]
    (aPats,aVars) = genPE' "num" n

    sumExps :: [Exp] -> Exp
    sumExps (h:t) = [| $h + $(sumExps t) |] --oops, can't do that
    sumExps []    = Lit $ Integer 0

\end{code}

But alas, the commented line is not the right type.

So how do I write genSummers?


peace,

isaac

ps. I implemented the printf and sel examples from the paper with the
real stuff from the GHC6 library, and that code can be found on the
wiki:

http://www.haskell.org/hawiki/TemplateHaskell

Maybe when I come up with a handful of nice examples I can add them to
the haddock for the Language.Haskell.THSyntax