Folks: if you are into the fine detail of the monomorphism
restriction then read on for a Haskell 98 wrinkle.  It's 
a fine point, and I'm only circulating it because I don't want
to make any un-announced changes to Haskell 98.

Simon



Mark [below] makes a good case, but I think it's quite evenly balanced.  

> | module M1 where             |       module M2 where
> |   x = factorial 20          |         y = let x = factorial 20 
> |   y = x + 2::Rational       |               in x + 2::Rational

Under the present scheme [option 2] both M1 and M2 are accepted.
Under the Jeff/Mark scheme [option 1], M1 is rejected but M2 is accepted.

Nevertheless, I agree that it is more reasonable to have
a difference between nested and top-level decls, than between
top-level decls within a module and top-level decls scattered
across modules.

So I'm happy to adopt option 1 for Haskell 98 unless someone
objects.

Simon

> -----Original Message-----
> From: Mark P Jones [mailto:[EMAIL PROTECTED]]
> Sent: Wednesday, November 18, 1998 4:15 PM
> To: Simon Peyton-Jones
> Cc: 'John Launchbury'; Jeffrey R. Lewis; Mark P Jones;
> [EMAIL PROTECTED]; [EMAIL PROTECTED]
> Subject: Re: monomorphism wierdness 
> 
> 
> I think we all agree and understand now that:
> 
>  1) Hugs does defaulting after each top-level binding group has
>     been processed.
> 
>  2) A Haskell compiler that conforms to the intentions of the report
>     will delay any such defaulting until each complete module has
>     been processed.
> 
> Initially, assuming that we think top-level bindings should be treated
> like local bindings, it seemed that option 2 would give the most
> consistent language design.  Jeff has been arguing instead 
> that option 1
> is better.  After a lot of thought, I'm strongly inclined to agree.
> 
> Here's the punchline:
> 
> Option 2 has serious flaws, and Haskell 98 should move to option 1.
> 
>                              -o-O-o-
> 
> 
> If you want the justification, take a deep breath and then read on:
> 
> Let's start by asking whether top-level binding groups really are just
> like local binding groups?  I think not, because there is a 
> fundamental
> difference.  The entire scope of a local binding is visible to a
> Haskell compiler.  By contrast, a top-level binding exported from a
> module M has a scope that includes, in effect, the set of all possible
> modules that import M.  So a compiler will *always* be able to see all
> of the ways in which a locally bound entity is used, but will *never*
> be able to see all of the ways in which an entity bound at the
> top-level will be used.
> 
> The only point where this distinction ceases to exist is at link-time:
> there, in the context of a particular program, you might reasonably
> consider that the scope of a definition can be completely 
> determined as
> being `the rest of the program'.
> 
> So, if we really believe that top-level and local bindings should
> be treated in the same way, then we shouldn't use option 2.  
> Defaulting
> at the module level is too early because we won't have seen the
> scope of the definitions.  Thus we should carry the monomorphic type,
> and the associated constraints, all the way to link time.  And only
> then might they be resolved, or trigger a type error.  (Of course, 
> neither of these will happen if the defined values are not actually
> used, but in that case we can simply treat the definition as dead
> code that does not appear in the final program.)
> 
> This doesn't sound too attractive from an engineering perspective,
> because we'd like to get earlier warnings of errors, and to depend
> only on existing linkers (which don't support this sophisticated
> kind of link-time type checking).
> 
> Meanwhile, let's look at the negative aspects of option 2, illustrated
> by one of Simon's examples:
> 
> | module M where              |       module M1 where
> |   x = factorial 20          |         x = factorial 20 
> |   y = x + 2::Rational       |
> |                                     |       module N where
> |                                     |         import M1
> |                                     |         y = x + 2::Rational
> 
> Assuming option 2, the example on the left will be accepted, but the
> example on the right will be rejected.  So modules are no longer just
> a way of structuring programs; they can actually change their 
> semantics!
> With option 1, these two programs are equivalent: both will 
> be rejected,
> unless perhaps the default default begins with Rational, in which case
> both will be accepted.  And in the first case, where both are 
> rejected,
> the same solutions can be used in each program to obtain an acceptable
> result.
> 
> Moreover, option 1 is consistent with other aspects of the Haskell
> design.  Independently, Simon and I have been discussing the way that
> kind inference for a datatype definition might be affected by later
> uses of that definition in the same module.  The Haskell report is
> quite clear on this: "Defaults are applied to each dependency group
> without consideration of the ways in which particular type constructor
> constants or classes are used in later dependency groups or elsewhere
> in the program."  Here, in the context of type inference, defaulting
> refers to the process of substituting * for any unbound variable in an
> inferred kind.  Nevertheless, I was still pretty amazed when 
> I realized
> how closely that particular choice of words coincides with 
> the topic of
> this discussion!
> 
> | So for Haskell 98 I think the thing to do is to make it clearer what
> | happens for top level things, perhaps using these examples.
> 
> I agree, but I also believe now that Option 2 is a poor 
> choice.  It fails
> to recognize a significant distinction between top-level and local
> bindings; it interacts badly with modularity; it is not 
> consistent with
> other aspects of the language.
> 
> Option 1 may not be ideal, but at least it has none of these 
> shortcomings.
> Haskell 98 should move to option 1.
> 
> All the best,
> Mark
> 
> 
> PS: On a personal note:  I didn't realize that Haskell 
> assumed option 2
> until several years after I'd written the core of the Gofer type
> checker, on which even the most recent versions of Hugs are still
> based.  Unfortunately, key features of the underlying 
> architecture make
> it very hard to support option 2, and I've long been embarassed at the
> resulting incompatibility here between Hugs and Haskell.  Removing the
> incompatibility has been on my long-term todo list for some time, and
> I confess that it never occurred to me to wonder whether the semantics
> specified in the report might actually be flawed.  Thanks for pursuing
> this Jeff, and helping me to become more enlightened!
> 


Reply via email to