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 String -> ExpQ, even though the input isn't syntactically quoted.

Suppose you have a slightly different example:

> > let x = 1 :: Int
> > runQ $ lift $ show x
> ListE [LitE (CharL '1')]
> > runQ [| show x |]
> AppE (VarE GHC.Show.show) (VarE x_1627398832)

With lift, the expression is evaluated, then the result '1' is lifted into
an AST.  But TH quotes do something entirely different: they lift *the
expression* into an AST.  In order to do so, the quoting mechanism needs to
parse its input string, then determine what each identifier is referring to.

When you're defining a function:

> > let p :: (Show a, Lift a) => a -> ExpQ; p n = [| show n |]

The quote has two terms: show and n.  'n' is a lambda-bound value, and show
is free. Free variables are looked up in the environment.  That's why we
see 'VarE GHC.Show.show' in the AST above; the fully-qualified Name is
generated and the AST references that name.  (numeric and string literals
are represented directly)

This is the key difference between this function definition and running the
splice above: in the function 'n' is lambda-bound, whereas in the above
splice 'x' is a free variable.

Lambda bindings can't be referenced by name because that name may not be in
scope when the generated splice is run.  Instead, lambda-bound values must
be lifted directly into the AST, which is exactly what 'lift' does.  If we
apply the function to a value, we can see the generated AST:

> > runQ (p 2)
AppE (VarE GHC.Show.show) (LitE (IntegerL 2))

The generated AST has the number 2, and applies the function  GHC.Show.show
to it.

If we want to show something that doesn't have a Lift instance, we can't do
it directly.  However, we can do this:

> > let q :: Show a => a -> ExpQ; q n = [| $(lift $ show n) |]
> > runQ (q 2)
> ListE [LitE (CharL '2')]

Note the differences.  We no longer require that 'n' has a Lift instance.
 However, the actual value of 'n' never appears in the AST!  Instead, we
first show 'n', then lift in the resulting string.  The order of operations
is changed too.  In the first case, the literal 2 is lifted into the AST
via lift, and the generated splice will apply show to that number whenever
the splice is run.  In the second case, (show 2) is evaluated first, then
the result is lifted into the AST (again via lift), causing that string to
be referenced within the splice.

HTH,
John




On Wed, Jul 3, 2013 at 5:44 AM, TP  wrote:

> 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"
> >> > $( lift "u" )
> >> "u"
> >>
> >> But if I replace a working version:
> >>
> >> pr n = [| putStrLn ( $(lift( nameBase n ++ " = " )) ++ show $(varE n) )
> >> |]   - case (i) -
> >>
> >> by
> >>
> >> pr n = [| putStrLn ( $([| (nameBase n) ++ " = " |]) ++ show $(varE n) )
> >> |]   - case (ii) -
> >>
> >> I again get the error
> >>
> >
> > In the working version, 'n' appears inside a splice, whereas in the other
> > n
> > is in a quote.  AFAIK any value can be used in a splice (provided it
> meets
> > the staging restrictions), whereas only Lift-able values can be used in a
> > quote.
>
> If I take this as a granted axiom, then I can admit the behavior above
> (error in case (ii), whereas it is working in case (i)) because n is a
> (Name), and so is not instance of Lift. Thus we are compelled to use lift
> instead of [||] (although the behavior is about the same for both in simple
> examples, as shown in my example above for "u").
>
> I do not understand the exact reason for that, but I can do without; and
> maybe it is better, because I am very probably not enough experienced to
> understand the details (and the reason is perhaps not trivial when I read
> Oleg who writes that what gives an error above in Haskell works in
> MetaOCaml).
>
> What is strange is that:
> * in the version using "lift", the definition of lift asks for the output
> of
> (nameBase n) to be an instance of Lift, what is the case because it is a
> string (cf my previous post in this thread).
> * whereas in the second version, we ask for n, not (nameBase n), to be an
> instance of Lift.
>
> Anyway, if we admit your axiom as granted, then we can also admit that the
> following version does not work (version of my initial post):
>
> >> >> pr :: Name -> ExpQ
> >> >> pr n = [| putStrLn $ (nameBase n) ++ " = " ++ show $(varE n) |]
>
> Thanks,
>
> TP
>
>
> ___
> Haskell-Cafe mailing list
>

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"
>> > $( lift "u" )
>> "u"
>>
>> But if I replace a working version:
>>
>> pr n = [| putStrLn ( $(lift( nameBase n ++ " = " )) ++ show $(varE n) )
>> |]   - case (i) -
>>
>> by
>>
>> pr n = [| putStrLn ( $([| (nameBase n) ++ " = " |]) ++ show $(varE n) )
>> |]   - case (ii) -
>>
>> I again get the error
>>
> 
> In the working version, 'n' appears inside a splice, whereas in the other
> n
> is in a quote.  AFAIK any value can be used in a splice (provided it meets
> the staging restrictions), whereas only Lift-able values can be used in a
> quote.

If I take this as a granted axiom, then I can admit the behavior above 
(error in case (ii), whereas it is working in case (i)) because n is a 
(Name), and so is not instance of Lift. Thus we are compelled to use lift 
instead of [||] (although the behavior is about the same for both in simple 
examples, as shown in my example above for "u").

I do not understand the exact reason for that, but I can do without; and 
maybe it is better, because I am very probably not enough experienced to 
understand the details (and the reason is perhaps not trivial when I read 
Oleg who writes that what gives an error above in Haskell works in 
MetaOCaml).

What is strange is that:
* in the version using "lift", the definition of lift asks for the output of 
(nameBase n) to be an instance of Lift, what is the case because it is a 
string (cf my previous post in this thread).
* whereas in the second version, we ask for n, not (nameBase n), to be an 
instance of Lift.

Anyway, if we admit your axiom as granted, then we can also admit that the 
following version does not work (version of my initial post):

>> >> pr :: Name -> ExpQ
>> >> pr n = [| putStrLn $ (nameBase n) ++ " = " ++ show $(varE n) |]

Thanks,

TP


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 |]

But if you have enough $( ) splices to balance out the [| |], there is
no lift involved:

myId1 x = $( [| x |] )
myId2 x = [| $(x) |]


I think your first example is supposed to do:

*Pr> let x = 5 in $(pr 'x)
x = 5

That's possible if you had defined pr as:

pr n = [| putStrLn $ $(lift (nameBase n)) ++ " = " ++ show $(varE n) |]

If there were no [| |] quotes, but still the ' syntax for getting a
Name, it would still be possible to define pr:

pr2 n
  = varE 'putStrLn `appE`
  (infixE (Just (lift (nameBase n))) (varE '(++))
 (Just
(infixE (Just (lift " = ")) (varE '(++))
   (Just (appE (varE 'show) (varE n))

--
Adam

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 instance.

Thanks John.
Ok I can understand that a Lift instance is needed, but to use the lift 
function below, we also need a Lift instance for the return of (nameBase n), 
because lift is a function that operates on instances of the Lift typeclass:

> :i lift
class Lift t where
  lift :: t -> Q Exp

And it is indeed the case:
> :i Lift
[...]
instance Lift a => Lift [a]
instance Lift Char

And as I have shown on a small example, lift and [||] return about the same 
result:

> runQ $ lift "u"
ListE [LitE (CharL 'u')
> runQ $ [| "u" |]
LitE (StringL "u")

So what is the difference between lift and [||]?
Although I feel stupid, I cannot lie and claim I have understood.

> Perhaps it helps if you think about what a quote does: it allows you to
> write essentially a string of Haskell code that is converted into an AST.
>  For this to work, the quote parser needs to know how to generate the AST
> for an identifier.  Like much of Haskell, it's type-driven.  For
> identifiers in scope from imports, TH simply generates a variable with the
> correct name.  But for data, the parser needs a way to generate an AST
> representation, which is what Lift is for.

Ok, I think I understand that (we need some method to transform a value at 
data level in a token of an AST), but it seems to me it does not answer my 
question above. But I am probably wrong.

Thanks

TP


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 function f, when applied to an Int (some bit pattern in a machine
> > register), produces _code_. It helps to think of the code
> > as a text string with the
> > source code. That text string cannot include the binary value that is
> > n. That binary value has to be converted to the numeric text string, and
> > inserted in the code. That conversion is called `lifting' (or
> > quoting). The function foo is accepted because Int is a liftable type,
> > the instance of Lift. And Name isn't.
>
> Thanks Oleg,
> Probably the following question will be stupid, but I ask it anyway: in my
> initial example, (nameBase n) returns a String, so we are not in the case
> where it is not "liftable"? In fact I am not sure to have understood your
> answer.
>

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 instance.


>
> 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"
> > $( lift "u" )
> "u"
>
> But if I replace a working version:
>
> pr n = [| putStrLn ( $(lift( nameBase n ++ " = " )) ++ show $(varE n) ) |]
>
> by
>
> pr n = [| putStrLn ( $([| (nameBase n) ++ " = " |]) ++ show $(varE n) ) |]
>
> I again get the error
>

In the working version, 'n' appears inside a splice, whereas in the other n
is in a quote.  AFAIK any value can be used in a splice (provided it meets
the staging restrictions), whereas only Lift-able values can be used in a
quote.

Perhaps it helps if you think about what a quote does: it allows you to
write essentially a string of Haskell code that is converted into an AST.
 For this to work, the quote parser needs to know how to generate the AST
for an identifier.  Like much of Haskell, it's type-driven.  For
identifiers in scope from imports, TH simply generates a variable with the
correct name.  But for data, the parser needs a way to generate an AST
representation, which is what Lift is for.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 machine
> register), produces _code_. It helps to think of the code
> as a text string with the
> source code. That text string cannot include the binary value that is
> n. That binary value has to be converted to the numeric text string, and
> inserted in the code. That conversion is called `lifting' (or
> quoting). The function foo is accepted because Int is a liftable type,
> the instance of Lift. And Name isn't.

Thanks Oleg,
Probably the following question will be stupid, but I ask it anyway: in my 
initial example, (nameBase n) returns a String, so we are not in the case 
where it is not "liftable"? In fact I am not sure to have understood your 
answer.

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"
> $( lift "u" )
"u"

But if I replace a working version:

pr n = [| putStrLn ( $(lift( nameBase n ++ " = " )) ++ show $(varE n) ) |]

by

pr n = [| putStrLn ( $([| (nameBase n) ++ " = " |]) ++ show $(varE n) ) |]

I again get the error 

"""
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'
"""

It is not easy to surmise the reason for this error.

TP


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 _code_. It helps to think of the code 
as a text string with the
source code. That text string cannot include the binary value that is
n. That binary value has to be converted to the numeric text string, and
inserted in the code. That conversion is called `lifting' (or
quoting). The function foo is accepted because Int is a liftable type,
the instance of Lift. And Name isn't. 

BTW, the value from the heap of the running program inserted into the
generated code is called `cross-stage persistent'. The constraint Lift
is implicitly generated by TH when it comes across a cross-stage
persistent identifier.  You can read more about it at
http://okmij.org/ftp/ML/MetaOCaml.html#CSP

Incidentally, MetaOCaml would've accepted your example, for now. There
are good reasons to make the behavior match that of Haskell.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
> 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


[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 :: 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