Typeable and 'forall' in data constructors
Simon Peyton-Jones
simonpj at microsoft.com
Thu Apr 22 10:20:27 EDT 2004
The code you gave looks fine to me, and indeed compiled.
But to fill out the instance declaration you'll need to
a) make Data the context in the App constructor
b) make Data the context in the instance Data (Term a) declaration
Also there is absolutely no point in the (Typeable a) context for the
data
declaration, so I dropped it.
Here's a filled-out version that works:
Simon
module Foo where
import Data.Typeable
import Data.Generics
data Term a
= Const a
| LVar Int
| forall b. Data b => App (Term (b -> a)) (Term b)
| Lam (Term a)
instance (Typeable a) => Typeable (Term a) where
typeOf w = mkAppTy (mkTyCon "Term.Term") [typeOf (undefined ::
a)]
instance (Data a) => Data (Term a) where
toConstr (Const _) = mkConstr 1 "Const" Prefix
toConstr (LVar _) = mkConstr 3 "LVar" Prefix
toConstr (App _ _) = mkConstr 4 "App" Prefix
toConstr (Lam _) = mkConstr 5 "Lam" Prefix
gmapT f (Const a) = Const (f a)
gmapT f (LVar i) = LVar (f i)
gmapT f (App t1 t2) = App (f t1) (f t2)
gmapT f (Lam t) = Lam (f t)
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org
[mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Akos Korosmezey
| Sent: 21 April 2004 13:23
| To: glasgow-haskell-users at haskell.org
| Subject: Typeable and 'forall' in data constructors
|
| I am tying to write a Term class with function application:
|
| data (Typeable a) => Term a =
| Const a |
| LVar Int |
| forall b. Typeable b => App (Term (b -> a)) (Term b) |
| Lam (Term a)
|
| Because 'forall' is present, ghc refuses to derive Typeable and Data
for
| Term. I tried to implement them:
|
| instance (Typeable a) => Typeable (Term a) where
| typeOf w = mkAppTy (mkTyCon "Term.Term") [typeOf (undefined ::
a)]
|
| instance (Typeable a) => Data (Term a) where
| toConstr (Const _) = mkConstr 1 "Const" Prefix
| toConstr (LVar _) = mkConstr 3 "LVar" Prefix
| toConstr (App _ _) = mkConstr 4 "App" Prefix
| toConstr (Lam _) = mkConstr 5 "Lam" Prefix
|
| But ghc 6.2.1 returns with error on the line 'toConstr (App _ _)...':
| parse error on input `b'. How can this be fixed?
| Thank you
|
| Akos Korosmezey
|
|
|
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list