Haskell 98 Report possible errors, part one

Olaf Chitil olaf@cs.york.ac.uk
Mon, 23 Jul 2001 15:11:32 +0100


Unfortunately both the old and the new situation are not so nice.
Both don't allow a simple translation of Haskell into the Haskell
kernel,
e.g. you cannot translate [1..] into Prelude.enumFrom 1, because the
latter may be ambiguous.

The following remark at the beginning of Section 3 is misleading:

Free variables and constructors used in these translations refer to
entities defined by the Prelude. To avoid clutter, we use True instead
of Prelude.True or map instead of Prelude.map. (Prelude.True is a
qualified name as described in Section 5.3.)

It implicitly suggests that a simple translation is possible.

Unfortunately I don't see any simple way to regain a simple translation.
Hence I just suggest to change the remark at the beginning of Section 3.
Just say that all free variables and constructors refer to entities
defined by the Prelude and warn that full qualification is in general
not sufficient to achieve this (because the entity may not be imported
and because of import .. as).

Ciao,
Olaf


> Marcin is right about this.  It is inconsistent as it stands.
> I propose to delete the sentence "The Preldue module
> is always available as a qualified import..." in the first
> para of 5.6.1.
> 
> The situation will then be:
>   if you don't import Prelude explicitly, you implicitly get
>         import Prelude
>   if you do import Prelude explicitly, you get no implicit imports
> 
> Nice and simple
> 
> | 5.6.1. "an implicit `import qualified Prelude' is part of
> | every module and names prefixed by `Prelude.' can always be
> | used to refer to entities in the Prelude". So what happens in
> | the following?
> |
> |     module Test (null) where
> |     import Prelude hiding (null)
> |     null :: Int
> |     null = 0
> |
> |     module Test2 where
> |     import Test as Prelude
> |     import Prelude hiding (null)
> |     x :: Int
> |     x = Prelude.null
> |
> | ghc allows that, it dosen't seem to implement the qualified
> | part of the implicit Prelude import. The report is
> | contradictory: adding `import qualified Prelude' makes
> | Prelude.null ambiguous, and thus names prefixed by `Prelude.'
> | can't always be used to refer to entities in the Prelude.

-- 
OLAF CHITIL, 
 Dept. of Computer Science, University of York, York YO10 5DD, UK. 
 URL: http://www.cs.york.ac.uk/~olaf/
 Tel: +44 1904 434756; Fax: +44 1904 432767