Unexpected NoImplicitPrelude behaviour in GHCi (bug?)

Philip K.F. Hölzenspies p.k.f.holzenspies at utwente.nl
Thu Jun 10 05:59:45 EDT 2010


Dear GHCers,

I have been experimenting some more with environments for lab work for
an FP intro course. One thing students tend to have difficulty with in
the initial labs are the error messages including type classes, or any
kind of more general type than they expected. I am trying to work around
this, by supplying a "Number" type for the first lab and gradually
increasing the complexity over the next few labs. To let all error
messages be in terms of my type, I use the NoImplicitPrelude option in a
LANGUAGE pragma. However, I find the behaviour of GHCi unexpected. I
have reduced the problem to a small case that reproduces the bug. Here
is my BugDemo module:

{-# LANGUAGE NoImplicitPrelude #-}
module BugDemo where
import qualified Prelude as P
newtype Number = N P.Integer
fromInteger = N

Look at the following sessions:


[holzensp at ewi1043:work/FPPrac]% ghci BugDemo.hs
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
[1 of 1] Compiling BugDemo          ( BugDemo.hs, interpreted )
Ok, modules loaded: BugDemo.
*BugDemo> 5
5
*BugDemo> :t 5
5 :: (P.Num t) => t
*BugDemo> :q
Leaving GHCi.
[holzensp at ewi1043:work/FPPrac]% ghci -fno-implicit-prelude BugDemo.hs
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
[1 of 1] Compiling BugDemo          ( BugDemo.hs, interpreted )

on the commandline:
    Warning: -fno-implicit-prelude is deprecated: use
-XNoImplicitPrelude or pragma {-# LANGUAGE NoImplicitPrelude #-} instead
Ok, modules loaded: BugDemo.
*BugDemo> 5

<interactive>:1:0: Not in scope: `>>'
*BugDemo> :t 5
5 :: Number
*BugDemo> 


It's a bit awkward that I get an explicit warning about
-fno-implicit-prelude being deprecated, while the behaviour is actually
different. Obviously, when leaving out the definition for fromInteger,
the second session fails whenever I type a number, whereas the first
session behaves the same way.

This seems to be me to be a bug.

Kind regards,
Philip



More information about the Glasgow-haskell-users mailing list