Simon's latest report changes the relationship between monomorphism
and defaulting. This issue was never discussed at length by the
committee so I think I'll bring the discussion out here.
In Haskell 1.4, top-level monomorphism could be resolved anywhere in
the module. Thus, this is perfectly valid Haskll 1.4:
module M where
x = 1
y :: Float
y = x + 1.0
Since x does not have a type signature, it is monomorphic but the use
of x in the context of y causes it to have the type Float.
In Hasklel 98, the proposal is to default the type of x to Integer
before doing type inference on y, resulting in a type error. This
appears to be the case whether or not x is exported. In an inner
declaration group, though, the old Haskell 1.4 rules apply, so that
let x = 1.0
y :: Float
y = x + 1
in ...
remains valid. The current version of the report (3rd revision) is
incorrect in that the example in 4.5.5,
module M where
len1 = genericLength "Hello"
len2 = (2*len1) :: Rational
will not typecheck and the explanation associated with it is not valid
- there is no difference between this example and the next one.
I object to this change for a number of reasons:
a) A stated goal of Haskell 98 were to make no unmotivated changes. I
don't believe any users requested this change. In fact, the only
result of this change is that more programs will have type erors.
b) This is a very confusing situation for novices. Programs that
appear to be quite valid are rejected (in a very odd way!) by the
type checker. I fail to see how this would make Haskell 98 any
better for teaching.
c) Code that works in a let may yield a type error when lifted to the
top level - very annoying.
d) The justifications presented for this change seem rather weak.
Symmetry with kind inference just doesnt get me excited: I never
write programs in which kind defaulting makes a difference, but I
constantly use numeric defaulting.
e) The new rule doesn't seem to be any simpler to explain than the old
one.
The old Hugs system implemented this new rule, rather by accident,
so I think we can say that this new rule has been thoroughly "tested".
My experience is that it is major pain in the ass, not an
improvement.
Please take the time look into this issue and voice your opinions.
John
Discussion:
The reason for all of this confusion is that in an ideal world,
monomorphism could be resolved across modules at the top level. This
the programs
module M where
x = 1
y :: Float
y = x + 1
and
module M1 where
x = 1
module M2 where
import M1
y :: Float
y = x + 1
would be the same. To get separate compilation to work, however,
previous Haskell reports stated that references outside the current
module cannot be used to resolve monomorhism. That is, after type checking
M1 we apply the default rule to x even though the use of x in M2 would
resolve the type of x. That is, we get rid of monomorphism after each
module is type checked. This is unfortunate but necessary unless we
want to restrict separate compilation. The new proposal treats each
declaration group in the same way as modules were handled in Haskell
1.4.