Coercion among existential types
Till Mossakowski
till@tzi.de
Wed, 10 Jul 2002 09:37:53 +0200
When implementing a tool for a heterogeneous language,
I want to write a coerce function that allows me
to coerce among different existential types:
-- use -fglasgow-exts -package lang
import Dynamic
class (Typeable id, Typeable as) =>
Syntax id as | id -> as
where parse :: id -> as
data HetSyntax = forall id as .
Syntax id as => HetSyntax id as
class (Syntax id as, Typeable env) =>
StaticAnalysis id as env | id -> as, id -> env
where analysis :: id -> as -> env
show_env :: id -> env -> String
data HetEnv = forall id as env .
StaticAnalysis id as env => HetEnv id as
coerce :: HetSyntax -> HetEnv
coerce (HetSyntax i a) =
case fromDynamic (toDyn (i,a)) :: (StaticAnalysis id as env=> Maybe (id,as))
of
Just (i1,a1) -> HetEnv i1 a1
Nothing -> error "No static analysis"
I have encountered the following error message:
Syntax3.hs:23:
Ambiguous type variable(s) `id', `as', `env'
in the constraint `StaticAnalysis id as env'
arising from use of `HetEnv' at Syntax3.hs:23
In a case alternative: HetEnv i1 a1
It seems that id, as, env are universally quantified.
Is there a way to make them dependent on the types of i and a?
Annotating i and a does not help:
coerce (HetSyntax (i::id) (a::as)) =
case fromDynamic (toDyn (i,a)) :: (StaticAnalysis id as env=> Maybe (id,as))
of
Just (i1,a1) -> HetEnv i1 a1
Nothing -> error "No static analysis"
leads to
Syntax3.hs:23:
Could not deduce (StaticAnalysis id as env)
from the context (Syntax id as)
Probable fix:
Add (StaticAnalysis id as env)
to the the existential context of a data constructor
arising from use of `HetEnv' at Syntax3.hs:23
In a case alternative: HetEnv i1 a1
What I want is that the coercion is successful iff there is an
instance of StaticAnalysis extending the given instance of
Syntax.
Till
--
Till Mossakowski Phone +49-421-218-4683
Dept. of Computer Science Fax +49-421-218-3054
University of Bremen till@tzi.de
P.O.Box 330440, D-28334 Bremen http://www.tzi.de/~till