[Haskell-cafe] Template haskell problem
Marc Weber
marco-oweber at gmx.de
Fri Jun 15 16:54:27 EDT 2007
I want to write a a template haskell function deriving show for data types without constructor.
-- example
-- data A a
-- the derived instance:
-- instance (Show a) => Show (A a) where
-- show _ = "A " ++ show (undefined :: a)
deriveShowNoConstructors :: Name -> Q [ Dec ]
deriveShowNoConstructors name = do
TyConI (DataD [] _ typeParams [] []) <- reify name
runIO $ putStrLn $ show typeParams
runIO $ hFlush stdout
return [ InstanceD (contexts typeParams)
(AppT (ConT nShow) (iOf (ConT name) typeParams))
[ FunD (mkName "show")
[Clause [WildP]
(NormalB (foldr (\a n -> InfixE (Just a) (VarE (mkName "++")) (Just n))
(LitE (StringL (pprint name)))
(map und typeParams))) -- <<< replacing occurs here (see below)
[] ]
] ]
where contexts = map (\n -> AppT (ConT nShow) (VarT n) ) -- ( ... ) =>
iOf = foldr (\n a -> AppT a (VarT n) ) -- ( ... ) where
nShow = mkName "Show"
und n = AppE (VarE (mkName "show")) (SigE (VarE (mkName "undefined")) (ForallT [n] [] (VarT n))) -- undefined :: typePara
But when trying to run it with:
data A a b c
[ .. module change ]
$( do l <- deriveShowNoConstructors ''A
runIO $ putStrLn $ pprint l
runIO $ hFlush stdout
return l )
I get the error:
src-HListMissing/HListMissingTest.hs|29| 3:
|| Ambiguous type variable `a[ad8]' in the constraint:
|| `Show a[ad8]'
|| arising from use of `show'
|| at src-HListMissing/HListMissingTest.hs:(29,3)-(32,13)
|| Probable fix: add a type signature that fixes these type variable(s)
||
src-HListMissing/HListMissingTest.hs|29| 3:
|| Ambiguous type variable `b[ada]' in the constraint:
|| `Show b[ada]'
|| arising from use of `show'
|| at src-HListMissing/HListMissingTest.hs:(29,3)-(32,13)
|| Probable fix: add a type signature that fixes these type variable(s)
||
src-HListMissing/HListMissingTest.hs|29| 3:
|| Ambiguous type variable `c[adc]' in the constraint:
|| `Show c[adc]'
|| arising from use of `show'
|| at src-HListMissing/HListMissingTest.hs:(29,3)-(32,13)
|| Probable fix: add a type signature that fixes these type variable(s)
When replacing typeParams with []
(thus only show _ = "Class" instead of show _ = "Class" ++ (undefined:: a) ++ ...
it compiles and prints the pretty printed abstract syntax tree as expected:
|| instance (Show a_0, Show b_1, Show c_2) => Show (THStuff.A c_2
|| b_1
|| a_0)
|| where show _ = "THStuff.A"
Do you see what I am doing wrong?
The function
und :: Name -> Exp
und n = AppE (VarE (mkName "show")) (SigE (VarE (mkName "undefined")) (ForallT [n] [] (VarT n)))
should create the (show $ undefined :: a)
part.
Marc Weber
More information about the Haskell-Cafe
mailing list