some questions about Template Haskell

Hi everybody, I am trying to learn Template Haskell, and I have two independent questions. 1/ First, the following code (which is not in its final version, but it is a test) does not compile: ------------------- {-# LANGUAGE TemplateHaskell #-} module Pr where import Language.Haskell.TH pr :: Name -> ExpQ pr n = [| putStrLn $ (nameBase n) ++ " = " ++ show $(varE n) |] ------------------- I obtain: ------------------- No instance for (Lift Name) arising from a use of `n' Possible fix: add an instance declaration for (Lift Name) In the first argument of `nameBase', namely `n' ------------------- Why? Indeed, there is no typeclass constraint on n in the definition of nameBase: ghci> :t nameBase nameBase :: Name -> String Contrary to lift for example: ghci> :t lift lift :: Lift t => t -> Q Exp 2/ If I define in a module: j = 3 and then define in another module: ------------------- h x = $([|j|]) main = do print $ h undefined ------------------- I obtain "3" as expected. However, I do not achieve to make this system work with an infix declaration: infix $([| j |]) + I obtain: parse error on input `$(' What is the problem? Thanks in advance, TP

TP wrote:
2/ If I define in a module:
j = 3
and then define in another module:
------------------- h x = $([|j|]) main = do print $ h undefined -------------------
I obtain "3" as expected.
However, I do not achieve to make this system work with an infix declaration:
infix $([| j |]) +
I obtain:
parse error on input `$('
I don't know what happens exactly, but one way to get out of this problem is to write the complete top-level declaration with a splice, instead of only the fixity level: $(return $ [ InfixD (Fixity $([| j |]) InfixN) (mkName "+") ]) Concerning my first question, I have not been able to understand what happens at this time. I continue to look at it. Thanks, TP

Hi TP, The reason that your initial example doesn't work is that Template Haskell splices can be used in four places: expressions, types, patterns (I think), and top-level declarations. The number in a fixity declaration is none of these. It's not an expression because you must write a literal number. However, the fixity declaration itself can be produced by a splice, and you've discovered that way out. About your first issue, I don't quite know what's going on there, either, I'm afraid. Richard On Jun 29, 2013, at 9:03 PM, TP wrote:
TP wrote:
2/ If I define in a module:
j = 3
and then define in another module:
------------------- h x = $([|j|]) main = do print $ h undefined -------------------
I obtain "3" as expected.
However, I do not achieve to make this system work with an infix declaration:
infix $([| j |]) +
I obtain:
parse error on input `$('
I don't know what happens exactly, but one way to get out of this problem is to write the complete top-level declaration with a splice, instead of only the fixity level:
$(return $ [ InfixD (Fixity $([| j |]) InfixN) (mkName "+") ])
Concerning my first question, I have not been able to understand what happens at this time. I continue to look at it.
Thanks,
TP
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Richard Eisenberg
-
TP