Re: [Haskell-cafe] some questions about Template Haskell

2013-07-02 Thread John Lato
lift and [| |] give similar results for that very stripped-down example, but it would be incorrect to extrapolate their behaviors from that case. They're executed at different times, by different mechanisms, and have vastly different behavior. It's also best to think of [| |] as having the type S

Re: [Haskell-cafe] some questions about Template Haskell

2013-07-02 Thread TP
John Lato wrote: >> Now, I have found another behavior difficult to understand for me: >> >> > runQ $ lift "u" >> ListE [LitE (CharL 'u') >> > runQ $ [| "u" |] >> LitE (StringL "u") >> >> So we have similar behaviors for lift and [||]. We can check it in a >> splice: >> >> > $( [| "u" |] ) >> "u"

Re: [Haskell-cafe] some questions about Template Haskell

2013-07-01 Thread adam vogt
On Mon, Jul 1, 2013 at 5:42 PM, TP wrote: > So what is the difference between lift and [||]? > Although I feel stupid, I cannot lie and claim I have understood. Hi TP, Sometimes [| |] does need to call lift. If for some reason the original lift wasn't exported, you could define: myLift x = [| x

Re: [Haskell-cafe] some questions about Template Haskell

2013-07-01 Thread TP
John Lato wrote: > The problem isn't the output of nameBase, it's the input parameter 'n'. > In your example, you've created a function that takes input (a Name) and > generates code based upon that input. In order to lift a value (n) from > an ordinary context into a quote, it needs a Lift inst

Re: [Haskell-cafe] some questions about Template Haskell

2013-06-30 Thread John Lato
On Mon, Jul 1, 2013 at 6:01 AM, TP wrote: > o...@okmij.org wrote: > > >> pr :: Name -> ExpQ > >> pr n = [| putStrLn $ (nameBase n) ++ " = " ++ show $(varE n) |] > > > > The example is indeed problematic. Let's consider a simpler one: > > > >> foo :: Int -> ExpQ > >> foo n = [|n + 1|] > > > > The

Re: [Haskell-cafe] some questions about Template Haskell

2013-06-30 Thread TP
o...@okmij.org wrote: >> pr :: Name -> ExpQ >> pr n = [| putStrLn $ (nameBase n) ++ " = " ++ show $(varE n) |] > > The example is indeed problematic. Let's consider a simpler one: > >> foo :: Int -> ExpQ >> foo n = [|n + 1|] > > The function f, when applied to an Int (some bit pattern in a mach

Re: [Haskell-cafe] some questions about Template Haskell

2013-06-30 Thread oleg
TP wrote: > pr :: Name -> ExpQ > pr n = [| putStrLn $ (nameBase n) ++ " = " ++ show $(varE n) |] The example is indeed problematic. Let's consider a simpler one: > foo :: Int -> ExpQ > foo n = [|n + 1|] The function f, when applied to an Int (some bit pattern in a machine register), produces _c

Re: [Haskell-cafe] some questions about Template Haskell

2013-06-29 Thread Richard Eisenberg
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

Re: [Haskell-cafe] some questions about Template Haskell

2013-06-29 Thread 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 > declar

[Haskell-cafe] some questions about Template Haskell

2013-06-28 Thread TP
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 ::