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 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe