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

Reply via email to