[Template-haskell] Problem with Labelled Fields

Eric Offermann eric.offermann@gmx.net
Thu, 26 Jun 2003 13:15:28 +0200


Hi!

Perhaps there's anybody out there who can help me with the following 
problem with labelled fields (using ghc 6.0).

The easy example modules are:

{- spliceC.hs -}
module spliceC where

import Language.Haskell.THSyntax

data C a = C
   {c_succ :: a -> a
   ,c_pred :: a -> a
   }

instance Lift (C a) where
   lift c =
     recCon "C"
       [fieldExp "c_succ" [| c_succ c |]
       ,fieldExp "c_pred" [| c_pred c |]
       ]

c_succS :: C a -> ExpQ
c_succS c = [| \ a -> c_succ c a |]

sampleC :: C Int
sampleC = C
   {c_succ = \ n -> n + 1
   ,c_pred = \ n -> n - 1
   }

{- main.hs -}
module Main where

import spliceC

sampleC_succ = $(c_succS sampleC)

I suppose that this should bring a function sampleC_succ into scope, 
instantiated for sampleC. But in fact I get
*** Exception: stack overflow

Who's wrong?

Thanks,
Eric