
Notwithstanding module Y, I don't think you should infer in module X that g::Int (or, rather, Int->Int). Since f is defined in a type class, it should be polymorphic, and so should g. When you apply g to a type, it will check to see what instances are available, and match only if Int is the type of the variable. But there's no reason to restrict the type of g itself. - Lyle camarao@dcc.ufmg.br wrote:
Informally, what I see as the defining rule for "closed world" is: "an expression is typed according to the set of definitions that are visible in the context in which it is used". Other possibilities exist, but the nice thing about this is that it is an extension of what happens without overloading.
With this definition, given _______________________ __________________________ | module X (f,g) where | | module Y where | | | | | | class A a where | | import X | | f :: a -> a | | | | instance A Int where | | instance A Float where | | f = id | | f x = x + 1.0 | | | | | | g x = f x | | h x = g x | ------------------------- --------------------------
we would infer: g::Int (since the context in g's definition has only f:Int) and thus h::Int in Y (since the context in h's definition has only one g::Int). If "h" was defined as "h x = f x" in Y, *then* it would have a polymorphic type (because there are two instances of "f" in Y).
Carlos
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe