
Hi, Could somebody try to compile these two files *TWICE*? GHC dumps core at me. I don't know if it is something about me, or something more general :) I'd like to know a bit more, before I bother anybody from devel team. Log: $ ghc --make THTest1.hs Chasing modules from: THTest1.hs Compiling THTest1TH ( ./THTest1TH.hs, ./THTest1TH.o ) Compiling THTest1 ( THTest1.hs, THTest1.o ) THTest1.hs:10:4: `incrSelf' is not a (visible) method of class `IncrSelf' $ ghc --make THTest1.hs Chasing modules from: THTest1.hs Skipping THTest1TH ( ./THTest1TH.hs, ./THTest1TH.o ) Compiling THTest1 ( THTest1.hs, THTest1.o ) Loading package base-1.0 ... linking ... done. Loading package haskell98-1.0 ... linking ... done. Loading package template-haskell-1.0 ... linking ... done. (here core dump, aka 0xc00000001) First of all, I do not understand the error in first compilation. Second, core dump is not nice :) My config: Windows XP Home, $ ghc -v Glasgow Haskell Compiler, Version 6.4, for Haskell 98, compiled by GHC version 6.2.2 Using package config file: c:\ghc\ghc-6.4\package.conf Using package config file: C:\Documents and Settings\gracjan\Application Data\ghc/i386-mingw32-6.4/package.conf Default windows package as taken from www.haskell.org. -- Gracjan {-# OPTIONS -fglasgow-exts -fth -fallow-undecidable-instances #-} module THTest1TH ( instanceIncrSelfTuple, IncrSelf(..) ) where import Control.Monad import Data.Maybe import Language.Haskell.TH class IncrSelf a where incrSelf :: a -> a instance Num a => IncrSelf a where incrSelf x = x + 1 sel' :: Int -> Int -> ExpQ sel' i n = lamE [pat] rhs where pat = tupP (map varP as) rhs = varE (as !! (i - 1)) as = map mkName [ ("a__" ++ show j) | j <- [1..n] ] instanceIncrSelfTuple :: Int -> Q [Dec] instanceIncrSelfTuple n = do decs <- qOfDecs let listOfDecQ = map return decs conIncrSelf = conT ''IncrSelf name_a = mkName "a" name_b = mkName "b" name_c = mkName "c" var_a = varT name_a var_b = varT name_b var_c = varT name_c dec <- instanceD (sequence [appT conIncrSelf var_a,appT conIncrSelf var_b]) (appT conIncrSelf (appT (appT (tupleT 2) var_a ) var_b ) ) listOfDecQ return [dec] where qOfDecs = [d| incrSelf value = let value1 = maybe Nothing (Just . fst) value value2 = maybe Nothing (Just . snd) value in error "adfasf" -- (incrSelf value1, incrSelf value2) |] {-# OPTIONS -fglasgow-exts -fth -fallow-undecidable-instances #-} module THTest1 where import THTest1TH instance IncrSelf String where incrSelf x = x ++ "x" $(instanceIncrSelfTuple 2)