
Okay (thanks to Simon PJ) - the problem appears to be that applying the improvement rules could result in a function being exported with an incorrect type signature (if a later module defines additional instances): module X (f,g) where class A a where f :: a -> a instance A Int where f = id g x = f x After appling improvement 'g's type would be "g::Int -> Int", however if we now do: module Y where import X instance A Float where f x = x + 1.0 h x = g x Then after the type sig exported for 'g' is wrong ... So my question is now: What if we don't improve the types of 'f' at all and leave it at its most general: "g :: A a => a -> a", and instead wait until we are tring to resolve overloading to apply improvement. IE at some point we must decide which dictionary to pass in, to the top level function (with a constraint "A a =>") what happens if we defer improvement till this point? Surely it must be safe to assume a closed class at the top level? Keean.

On Thu, Aug 12, 2004 at 06:37:20PM +0100, MR K P SCHUPKE wrote:
Surely it must be safe to assume a closed class at the top level?
This could be a source of unpleasant surprises, ie. something works at top level, but breaks when you move it to some module. If by top level you also mean Main (as opposed to interactive "toplevel"), it would be much more surprising. I often experiment by writing a single module program and split it to many modules later. Anyway, (with extensions) it is possible to write code which would be broken by closed world at top level, for example: g :: (forall a. A a => a -> a) -> something and somewhere else ... (g f) ... Best regards, Tom -- .signature: Too many levels of symbolic links

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

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

Notwithstanding module Y, I don't think you should infer in module X that g::Int (or, rather, Int->Int).
Oops, I meant Int->Int.
Since f is defined in a type class, it should be polymorphic, and so should g. When you apply g to [an expression of a given] 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.
Sorry I wasn't clear: I meant to be talking about (an approach for) "closed classes".

G'day all. Quoting camarao@dcc.ufmg.br:
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.
Except that you can choose to export or not export a non-overloaded function from a module, but you don't have that choice with typeclass instances. Cheers, Andrew Bromage
participants (6)
-
ajb@spamcop.net
-
camarao@dcc.ufmg.br
-
Carlos Camarão
-
Lyle Kopnicky
-
MR K P SCHUPKE
-
Tomasz Zielonka