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