
2010/9/14 Kevin Jardine
I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has some code suggestions or pointers to something similar?
The solutions first: ------------------------------------------------- {-# LANGUAGE TemplateHaskell #-} module T(mkNewType) where import Language.Haskell.TH decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|] decl = do [d] <- decls runIO $ print d -- just to show inetrnals return d mkNewType :: String -> Q [Dec] mkNewType n = do d <- decl let name = mkName n return $ (\x -> [x]) $ case d of (NewtypeD cxt _ argvars (NormalC _ args) derivings) -> NewtypeD cxt name argvars (NormalC name args) derivings -------------------------------------- I took perfectly valid declaration, dissected it using case analysis and changed relevant parts. And an example client: ------------------------------------- {-# LANGUAGE TemplateHaskell #-} import T $(mkNewType "A") ------------------------------------- It all work together. I studied how to use Template Haskell that way: I obtained declarations of what I need, printed them and looked through documentation for relevant data types and constructors. It's not harder that any other library in Haskell, actually.