Template Haskell...
MR K P SCHUPKE
k.schupke at imperial.ac.uk
Fri Oct 31 13:23:39 EST 2003
With reference to the future of template haskell - it would be nice if you could express the
following:
stringType :: String -> Q [Dec]
stringType s = do
x <- gensym "x"
y <- gensym "y"
return [
Newtype [] s [] (Constr s [(Strict,Tcon (TconName "String"))]) [],
Proto ("show"++s) (Tapp (Tapp (Tcon Arrow) (Tcon (TconName s))) (Tcon (TconName "ShowS"))),
Fun ("show"++s) [Clause [Pcon s [Pvar x]]
(Normal (App (Var "showString") (Var x))) []],
Instance [] (Tapp (Tcon (TconName "Show")) (Tcon (TconName s))) [
Fun "showsPrec" [Clause [Pwild,Pvar x]
(Normal (App (Var ("show"++s)) (Var x))) []]],
Instance [] (Tapp (Tcon (TconName "Eq")) (Tcon (TconName s))) [
Fun "==" [Clause [Pcon s [Pvar x],Pcon s [Pvar y]]
(Normal (App (App (Var "==") (Var x)) (Var y))) []]] ]
AS
stringType :: String -> Q [Dec]
stringType s = [|
newtype $s = $s String
show$s :: $s -> ShowS
show$s ($s x) = showString x
instance Show $s where
showsPrec _ x = show$s x
instance Eq $s where
($s x) ($s y) = (x==y)
|]
Maybe with a more specific type like :
stringType :: TypeName -> Q [Dec]
where TypeName would enforce the first letter must be capital rule.
NOTE: to work this would require show$s to crate a function name from
show prepended to the type name...
Why is this not possible with the current template-haskell, and would
this be possible with the proposed extensions (if not, why not, as the
above seems very easy to read?)
Regards,
Keead Schupke.
More information about the Glasgow-haskell-users
mailing list