The question I have is this.  In the example you gave the type signatures
for both versions of reverse are identical, are they not?  If they are
identical, I don't see the harm in not qualifying the type signatures.  On
the other hand, suppose they were not identical.  If there are no argument
types that would satisfy both versions, again there is no problem.  A
problem seems to arise when when the same argument could be applied to
either version.  So my question is, perhaps the qualifier could be required
in the type signature only if the type signatures are different?

 

> -----Original Message-----
> From: Simon Peyton-Jones [mailto:[EMAIL PROTECTED]]
> Sent: Friday, June 09, 2000 10:17 AM
> To: '[EMAIL PROTECTED]'
> Cc: Simon Peyton-Jones
> Subject: When is an occurrence an occurrence
> 
> 
> Gentle Haskellers,
> 
> Here's a Haskell98-typo question.
> 
> Consider this program:
> 
>       module M where
> 
>       reverse xs = Prelude.reverse (tail xs)
> 
>       foo ys = M.reverse ys
> 
> This is legal Haskell98.  The call to Prelude.reverse and to M.reverse
> must both be qualified, because plain 'reverse' would be ambiguous.
> But the definition of reverse does not need to be qualified, 
> becuase it's
> a definition!
> 
> 
> Now, would it be legal to add this type signature to the end of M?
> 
>       reverse :: [a] -> [a]
> 
> Or should it be
> 
>       M.reverse :: [a] -> [a]
> 
> I can see two arguments
> 
> A) The unqualified form should be legal because the type signature 
>       can only refer to the 'reverse' defined in this module
> 
> B) The unqualified form is ambiguous.  All occurrences of 'reverse', 
>       other than the definition itself, must be qualified
> 
> The Report itself does not answer the question clearly,
> so I propose to resolve the ambiguity.
> 
> Personally I'm inclined to resolve it in favour of (B).  In 
> due course we
> may want to allow type signatures for imported things in a 
> module, for 
> example.  Does anyone object?
> 
> Simon
> 

Reply via email to