RE: [Haskell-cafe] Template Haskell -- when are things evaluated?

2008-04-02 Thread Simon Peyton-Jones
|  I'm reading the following rule from your answer:
| 
|   [|exp|] normally returns the unevaluated AST of exp. However, if exp
| contains
|   local variables, these are lifted using Language.Haskell.TH.lift (i.e.
| evaluated
|   before lifting).
| 
|   Is that correct?
| 
| 
|   / Emil
|
| Yes, that seems to be true. I'm not an expert in the internals of TH
| though, so I have inferred that rule by extensive use of TH ;).
|
| SPJ can confirm if it's right.

Sorry, been busy with the ICFP deadline.

I think you are asking this:

module M(f) where

  f :: Int - Q Exp
  f x = let  expensive :: Int - Int
 expensive p = p*p + x*x

in let y = expensive x

in [| y+1 |]

module Test where
  import M
  test n = n + $(f 4)

When compiling module Test, TH will evaluate (f 4), returning a syntax tree 
which it will splice in place of the call $(f 4).  What expression will it 
return?  Two candidates:

  $(f 4) --  24+1
  $(f 4) --  expensive 4 + 1

In TH you get the former, which is I think what you understood.  Why?  Apart 
from anything else, 'expensive' isn't even in scope in module Test -- it was a 
local binding inside the invocation of f.  Second, this is partly what staging 
is about; you get to specify when you want things to be done. If you want the 
splice to contain the call to expensive (rather than its result), you'll need 
to float out expensive to the top level (which means lambda-lifting).  And then 
you can say this:

  expensive :: Int - Int - Int
  expensive x p = p*p + x*x

  f :: Int - Q Exp
  f x = let y = [| expensive x x |]

in [| $y+1 |]

By putting the call in a quote we delay its evaluation.

If someone felt like transcribing this little thread into a FAQ-like thing on 
the GHC user wiki (I'm disconnected at the moment) that would be a fine thing 
to do.  Thanks.

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


[Haskell-cafe] Template Haskell -- when are things evaluated?

2008-03-13 Thread Emil Axelsson

Hello all!

Up until yesterday I thought I understood the basics of Template Haskell, but 
now I'm a little confused. Consider the following code


module A
  where
a1 = [| (2::Int) + 2 |]

a2 = let x = (2::Int) + 2 in [| x |]

a3 = [| y |]
  where
y = (2::Int) + 2

z = (2::Int) + 2

a4 = [| z |]

module B
  where
import A

a1S = $a1
a2S = $a2
a3S = $a3
a4S = $a4

I'd have thought that in all four cases the addition was evaluated at 
compile-time, but compiling with -ddump-splices reveals that this is only the 
case for a2 and a3. Is there a general reliable rule for when things are evaluated?


Thanks,

/ Emil

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


Re: [Haskell-cafe] Template Haskell -- when are things evaluated?

2008-03-13 Thread Alfonso Acosta
Hi Emil,

Your  problem is related to how are things evaluated not when. The
short answer is: if you want to make sure an expression is evaluated
before you lift it, don't use quasiquotes, call
Language.Haskell.TH.lift

On Thu, Mar 13, 2008 at 9:00 AM, Emil Axelsson [EMAIL PROTECTED] wrote:
  a1 = [| (2::Int) + 2 |]

You are lifting the expression AST, not its evaluation. a1 = lift
((2::Int) + 2) would work as you want.


  a2 = let x = (2::Int) + 2 in [| x |]

here you are enclosing a local variable in quasiquotes and, thus, [| x
|] is equivalent to lift x

  a3 = [| y |]
where
  y = (2::Int) + 2

Same as in a2, y is local. Therefore [| y |] is equivalent to lift y

  z = (2::Int) + 2

  a4 = [| z |]

z is a global variable and [| z |] is lifted to a variable expression
(i.e. a4 is equivalent to varE 'z  )
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell -- when are things evaluated?

2008-03-13 Thread Emil Axelsson
Aha, I guess I thought for a while that [|x|] and  lift x  where the same thing. 
Having thought too much about partial evaluation lately, I forgot that the main 
purpose of quoting is to get the unevaluated AST.


I'll just use lift in the future then (for partial evalutation).

Thanks, Alfonso!

/ Emil



On 2008-03-13 09:49, Alfonso Acosta wrote:

Hi Emil,

Your  problem is related to how are things evaluated not when. The
short answer is: if you want to make sure an expression is evaluated
before you lift it, don't use quasiquotes, call
Language.Haskell.TH.lift

On Thu, Mar 13, 2008 at 9:00 AM, Emil Axelsson [EMAIL PROTECTED] wrote:

 a1 = [| (2::Int) + 2 |]


You are lifting the expression AST, not its evaluation. a1 = lift
((2::Int) + 2) would work as you want.



 a2 = let x = (2::Int) + 2 in [| x |]


here you are enclosing a local variable in quasiquotes and, thus, [| x
|] is equivalent to lift x


 a3 = [| y |]
   where
 y = (2::Int) + 2


Same as in a2, y is local. Therefore [| y |] is equivalent to lift y


 z = (2::Int) + 2

 a4 = [| z |]


z is a global variable and [| z |] is lifted to a variable expression
(i.e. a4 is equivalent to varE 'z  )

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


Re: [Haskell-cafe] Template Haskell -- when are things evaluated?

2008-03-13 Thread Emil Axelsson

I'm reading the following rule from your answer:

[|exp|] normally returns the unevaluated AST of exp. However, if exp contains 
local variables, these are lifted using Language.Haskell.TH.lift (i.e. evaluated 
before lifting).


Is that correct?

/ Emil



On 2008-03-13 09:49, Alfonso Acosta wrote:

Hi Emil,

Your  problem is related to how are things evaluated not when. The
short answer is: if you want to make sure an expression is evaluated
before you lift it, don't use quasiquotes, call
Language.Haskell.TH.lift

On Thu, Mar 13, 2008 at 9:00 AM, Emil Axelsson [EMAIL PROTECTED] wrote:

 a1 = [| (2::Int) + 2 |]


You are lifting the expression AST, not its evaluation. a1 = lift
((2::Int) + 2) would work as you want.



 a2 = let x = (2::Int) + 2 in [| x |]


here you are enclosing a local variable in quasiquotes and, thus, [| x
|] is equivalent to lift x


 a3 = [| y |]
   where
 y = (2::Int) + 2


Same as in a2, y is local. Therefore [| y |] is equivalent to lift y


 z = (2::Int) + 2

 a4 = [| z |]


z is a global variable and [| z |] is lifted to a variable expression
(i.e. a4 is equivalent to varE 'z  )

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


Re: [Haskell-cafe] Template Haskell -- when are things evaluated?

2008-03-13 Thread Alfonso Acosta
On Thu, Mar 13, 2008 at 11:13 AM, Emil Axelsson [EMAIL PROTECTED] wrote:
 I'm reading the following rule from your answer:

  [|exp|] normally returns the unevaluated AST of exp. However, if exp contains
  local variables, these are lifted using Language.Haskell.TH.lift (i.e. 
 evaluated
  before lifting).

  Is that correct?


  / Emil

Yes, that seems to be true. I'm not an expert in the internals of TH
though, so I have inferred that rule by extensive use of TH ;).

SPJ can confirm if it's right.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe