Unexpected NoImplicitPrelude behaviour in GHCi (bug?)

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@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@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

Dear GHCers, With regards to the e-mail below, I have done one more test and found that ghci -fno-implicit-prelude and ghci -XNoImplicitPrelude behave the same. However, I'm still a little taken aback by the use thereof. Consider two files Foo.hs and Bar.hs: Foo.hs: {-# LANGUAGE NoImplicitPrelude #-} module Foo where import Bar fromInteger _ = () fromRational _ = () _ >> a = bar a Bar.hs: module Bar where bar = id If I load Foo into GHCi, I arrive at a prompt with a subset of the Prelude in the context. Consider the following: *Foo> :t map <interactive>:1:0: Not in scope: `map' *Foo> :t 5 5 :: (GHC.Num.Num t) => t *Foo> 5 5 *Foo> If I load Foo into GHCi with an explicit command-line option -XNoImplicitPrelude, module Bar fails to compile, because 'id' is unknown. If I add an explicit import of the Prelude to Bar, running ghci with the command-line option results in: *Foo> :t map <interactive>:1:0: Not in scope: `map' *Foo> :t 5 5 :: () *Foo> 5 () *Foo> Shouldn't the expected behaviour of GHCi be that the "entry module" determines the entire context? In other words, if module X in ghci X or in ghci
:l X
contains the LANGUAGE-pragma NoImplicitPrelude, should the Prelude not be unloaded from ghci? I would argue that this might also be seen as an example of why Ticket #124 for haskell-prime is a good idea for GHC: http://hackage.haskell.org/trac/haskell-prime/ticket/124 Kind regards, Philip On Thu, 2010-06-10 at 11:59 +0200, Philip K.F. Hölzenspies wrote:
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@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@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
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Thursday 10 June 2010 14:02:10, Philip K.F. Hölzenspies wrote:
Dear GHCers,
<snip>
Shouldn't the expected behaviour of GHCi be that the "entry module" determines the entire context? In other words, if module X in
ghci X
or in
ghci
:l X
contains the LANGUAGE-pragma NoImplicitPrelude, should the Prelude not be unloaded from ghci?
I don't think so. LANGUAGE-pragmata are a per-module thing. If you want to do some NoImplicitPrelude stuff in one module and test that module in ghci, most of the time you still want to have the Prelude functions around. Your use-case seems more an exception to me.
I would argue that this might also be seen as an example of why Ticket #124 for haskell-prime is a good idea for GHC:
Hmm, I'd then have to explicitly import the Prelude in all my source files. I could live with it, but I prefer the current behaviour.
Kind regards, Philip

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.
Wasn't that the rationale for developing / using Helium? http://www.cs.uu.nl/wiki/bin/view/Helium/Features
However, I find the behaviour of GHCi unexpected.
There are some oddities in the handling of options/pragmas wrt GHCi, as discussed in this ticket: http://hackage.haskell.org/trac/ghc/ticket/3217 At the moment, and as far as options/pragmas are concerned, the GHCi prompt can be seen as an importer of the modules loaded. So it needs its own option settings, even if you load *Main and the Main.hs source code has language pragmas. This can be confusing (eg, *Main otherwise means "treat expressions at GHCi prompt as if it was in the Main module"). The consensus in that ticket was that the separation of commandline options, GHCi session options, and source pragmas could be clearer, and there was a concrete proposal for a pragmatic implementation plan to improve consistency (just waiting for an implementer;-). Claus

Dear Claus, et al. I've already responded in more detail in another e-mail on the seemingly inconsistent behaviour of GHCi, but I also wanted to respond to your points here. On Jun 10, 2010, at 4:15 PM, Claus Reinke wrote:
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.
Wasn't that the rationale for developing / using Helium?
This is true. Having said that, I find GHC's error messages to be reasonably good and I find GHC as a compiler to be better. Also, I don't believe very much in their philosophy. I don't think teaching aides that tell a student precisely what to do are necessarily better. The only downside (from a teaching point of view) of GHC's error messages, is that you have to know and understand so much of Haskell to read them. I want GHC's error messages, but just restricted to non-typeclass issues. I'm hoping this will stimulate students to actually read the error messages. Once they're confident that they're actually really informative, I don't mind when they get a little messy ;)
There are some oddities in the handling of options/pragmas wrt GHCi, as discussed in this ticket:
Thanks for the pointer.
At the moment, and as far as options/pragmas are concerned, the GHCi prompt can be seen as an importer of the modules loaded. So it needs its own option settings, even if you load *Main and the Main.hs source code has language pragmas. This can be confusing (eg, *Main otherwise means "treat expressions at GHCi prompt as if it was in the Main module").
I agree; I would like *Main to mean "it's as if you're now inside the Main module".
The consensus in that ticket was that the separation of commandline options, GHCi session options, and source pragmas could be clearer, and there was a concrete proposal for a pragmatic implementation plan to improve consistency (just waiting for an implementer;-).
Mmm... time :( Regards, Philip

On Jun 10, 2010, at 05:59 , Philip K.F. Hölzenspies wrote:
[holzensp@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@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: `>>'
This doesn't surprise me; when putting it in the module, it affects only that module. When using either command line version, it affects *everything*... and what's breaking is not your definition of Number, but the ghci expression printer (which, being in IO, is doing something like (print it >> putStr "\n"). Since the command line option has global effect, the Prelude's (>>) isn't defined for ghci's guts either. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Jun 11, 2010, at 5:10 AM, Brandon S. Allbery KF8NH wrote: <snip>
This doesn't surprise me; when putting it in the module, it affects only that module. When using either command line version, it affects *everything*... and what's breaking is not your definition of Number, but the ghci expression printer (which, being in IO, is doing something like (print it >> putStr "\n"). Since the command line option has global effect, the Prelude's (>>) isn't defined for ghci's guts either.
Your explanation would make perfect sense to me; pragma's in the module effect only the module. This is, however, nog GHCi's behaviour. If I have a module that's only this: {-# LANGUAGE NoImplicitPrelude #-} module Foo where and I open this in GHCi, I get the following session: Ok, modules loaded: Foo. *Foo> 42 42 *Foo> 42.0 42.0 *Foo> :t 42 42 :: (GHC.Num.Num t) => t *Foo> 40 + 2 <interactive>:1:3: Not in scope: `+' *Foo> :t fromRational <interactive>:1:0: Not in scope: `fromRational' *Foo> This means that there is *some* definition of fromInteger, fromRational and (>>), but it's not accessible for me at the prompt. Types and typeclasses seem to be imported fully qualified. I would either expect GHCi to start complaining when I type 42, or to not complain about any of these above commands. Any thoughts? Regards, Philip
participants (5)
-
"Philip K.F. Hölzenspies"
-
Brandon S. Allbery KF8NH
-
Claus Reinke
-
Daniel Fischer
-
Philip K.F. Hölzenspies