[Haskell-cafe] [Template Haskell Question] On defining recursive templates.

Dominik Bollmann dominikbollmann at gmail.com
Wed Jan 20 19:01:34 UTC 2016


Hello Haskellers,

I'm currently diving into Template Haskell and I just read the
original TH paper [1]. There they give the following example of a
generic zip function:

-- | A generic zip function. Use (e.g.,) as $(zipN 3) xs ys zs.
zipN :: Int -> ExpQ
zipN n = [| let zp = $(mkZip n [| zp |]) in zp |]

-- | Helper function for zipN.
mkZip :: Int -> ExpQ -> ExpQ
mkZip n contZip = lamE pYs (caseE (tupE eYs) [m1, m2])
  where
    (pXs, eXs)   = genPEs "x" n 
    (pXSs, eXSs) = genPEs "xs" n
    (pYs, eYs)   = genPEs "y" n
    allCons      = tupP $ zipWith (\x xs -> [p| $x : $xs |]) pXs pXSs
    m1           = match allCons continue []     
    m2           = match wildP stop []
    continue     = normalB [| $(tupE eXs) : $(appsE (contZip:eXSs))|]
    stop         = normalB (conE '[])

-- | Generates n pattern and expression variables.
genPEs :: String -> Int -> ([PatQ], [ExpQ])
genPEs x n = (pats, exps)
  where names        = map (\k -> mkName $ x ++ show k) [1..n]
        (pats, exps) = (map varP names, map varE names)

This works as expected, e.g., `$(zipN 3) [1..3] [4..6] [7..9]' gives
[(1,4,7),(2,5,8), (3,6,9)].

However, I found this definition of passing `[| zp |]' as a helper
function slightly confusing, so I tried to make it more succinct and to
call zipN directly in the recursion:

zipN' :: Int -> ExpQ
zipN' n = lamE pYs (caseE (tupE eYs) [m1, m2])
  where
    (pXs, eXs)   = genPEs "x" n 
    (pXSs, eXSs) = genPEs "xs" n
    (pYs, eYs)   = genPEs "y" n
    allCons      = tupP $ zipWith (\x xs -> [p| $x : $xs |]) pXs pXSs
    m1           = match allCons continue []     
    m2           = match wildP stop []
    continue     = normalB [| $(tupE eXs) : $(appsE (zipN n:eXSs)) |]
    stop         = normalB (conE '[])

This subtle change, however, causes the compiler to diverge and to get
stuck at compiling splice `$(zipN' 3) [1..3] [4..6] [7..9]'...

Could anyone explain to me why the first approach works, but the 2nd
small deviation does not? Is it because the compiler keeps trying to
inline the recursive call to (zip N) into the template indefinitely?

Are there easier (more straightforward) alternative implementations to
the (imo) slightly convoluted example of zipN from the paper?

Any hints are very much appreciated.

Thanks,
Dominik.

[1] http://research.microsoft.com/~simonpj/papers/meta-haskell/


More information about the Haskell-Cafe mailing list