On 28-Apr-1999, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote:
> Folks,
> 
> Here's a good Haskell 98 question: is this a valid H98 module?
> 
>       module F where
>               sin :: Float -> Float
>               sin x = (x::Float)
> 
>               f :: Float -> Float
>               f x = Prelude.sin (F.sin x)
> 
> The 'sin' function is defined by the (implicitly imported) Prelude.
> It's OK to define a local sin function.
> In the definition of 'f', the two different sin functions are called.
> 
> The question is this: is the type signature for 'sin' OK?  The
> syntax of H98 doesn't allow a qualified name here, so presumably
> there is only one 'sin' that can possibly be meant by this signature,
> namely F.sin.
> 
> But this isn't explicit in the H98 report.  And the same applies to
> fixity declarations.
> 
> I propose to treat it as a typo, and add a clarifying remark 
> to Section 5.5.2 (name clashes) that makes it clear that type signatures
> and fixity declarations are always unqualified, and refer (of course)
> to the variable bound in the same declaration group as the type
> sig or fixity decl.
> 
> Please yell if this is a stupid thing to do.

That sounds like a fine thing to do if the signature is unqualified.
But it should also be legal to use an explicit qualifier, so long as you
specify the same module that would be used if the signature was unqualified.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh>  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]        |     -- the last words of T. S. Garp.


Reply via email to