deriving data Foo = Foo { unFoo :: String } ?
============= TestX.hs ============================================== module TestX where import Language.Haskell.TH import Language.Haskell.TH.Syntax mkADT :: String -> String -> Q [Dec] mkADT n t = let n' = mkName n un = mkName $ "un" ++ n in return [DataD [] n' [] [RecC n' [(un,NotStrict,ConT un)]] []] ============= Main.hs ================================================ -- peckages: template-haskell {-# OPTIONS_GHC -XTemplateHaskell #-} module Main where import TestX $( mkADT "Test" "String") main = putStrLn . unTest $ Test "test" ============= error ================================================== test.hs|1 error| || Illegal type constructor or class name: `unTest' || When splicing generated code into the program ============= ======================================================= What am I doing wrong? Thanks Marc Weber
Hello Marc, Sunday, May 25, 2008, 4:51:14 PM, you wrote:
in return [DataD [] n' [] [RecC n' [(un,NotStrict,ConT un)]] []]
this probably eq to: data Test = {unTest :: unTest} last unTest is in the type name position
test.hs|1 error| || Illegal type constructor or class name: `unTest' || When splicing generated code into the program
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (2)
-
Bulat Ziganshin -
Marc Weber