[GHC] #10920: ghci can't load local Prelude module

#10920: ghci can't load local Prelude module -------------------------------------+------------------------------------- Reporter: Yuras | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | -------------------------------------+------------------------------------- I have a `Prelude.hs` file which contains {{{#!hs module Prelude where }}} If I invoke `ghci` from the same directory, I get {{{ Top level: attempting to use module ‘Prelude’ (./Prelude.hs) which is not loaded }}} Note: `ghc --make` correctly compiles modules that use the local `Prelude.hs`, so I expect `ghci` to handle that case too. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10920 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10920: ghci can't load local Prelude module -------------------------------------+------------------------------------- Reporter: Yuras | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): -------------------------------------+------------------------------------- Changes (by osa1): * cc: osa1 (added) Comment: I once reported this in IRC channel but IIRC someone had convinced me that this is not a bug. Maybe that person can write the explanation here. (I don't remember who) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10920#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10920: ghci can't load local Prelude module -------------------------------------+------------------------------------- Reporter: Yuras | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gelisam): osa1, I am not that person, but here is an explanation. If you have a file called `./Foo.hs` and you try to import it, `ghci` tells you that it doesn't know about that file, because you haven't loaded it yet: {{{ $ ghci GHCi, version 7.10.2: http://www.haskell.org/ghc/ :? for help Prelude> import Data.List <no location info>: Could not find module ‘Foo’ It is not a module in the current program, or in any known package. }}} The solution is to run `:load Foo.hs` before `import Foo`. If you have a file called `./Data/List.hs`, this now conflicts with the `Data.List` from `base`, so you get a different message clarifying which module is not loaded: {{{ $ ghci GHCi, version 7.10.2: http://www.haskell.org/ghc/ :? for help Prelude> import Data.List <interactive>:1:1: attempting to use module ‘Data.List’ (./Data/List.hs) which is not loaded }}} The solution is to run `:load Data/List.hs` before `import Data.List`. Now without `-XNoImplicitPrelude`, `ghci` begins by running `import Prelude`, which normally succeeds by loading the Prelude from `base`, but in this case, since there is a `./Prelude.hs` file, `ghci` tells you that it can't use that file because it isn't loaded yet. Since the user didn't explicitly type `import Prelude`, the error message is confusing, so maybe there should be some special logic to give a different message in that case or even to implicitly `:load ./Prelude.hs`. Note, however, that there are other modules than Prelude which can trigger this error message when particular files are present and the user hasn't explicitly typed an import statement. If your `.ghci` has an `import Data.List` intended to import the `Data.List` from `base`, it will usually work, until you have a local file called `./Data/List.hs` in which case `ghci` will complain on startup with this same message that it can't use `./Data/List.hs` because it is not loaded. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10920#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10920: ghci can't load local Prelude module -------------------------------------+------------------------------------- Reporter: Yuras | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by phadej): A workaround which seems to work for hackage-security: First: write a .ghci file with: {{{ :load src/Prelude.hs import Prelude :set -XImplicitPrelude }}} As cabal doesn't give ability to pass /only/ ghci-flags atm use `cabal repl -v` or `cabal new-repl -v` to get a command line cabal uses: something like {{{ /opt/ghc/8.0.1/bin/ghc --interactive -fbuilding-cabal-package -O0 -outputdir ... }}} then add a `-XNoImplicitPrelude` there {{{ /opt/ghc/8.0.1/bin/ghc --interactive -XNoImplicitPrelude -fbuilding-cabal- package -O0 -outputdir ... }}} --- This works because - if `-XNoImplicitPrelude` is specified `ghci` doesn't implicitly load Prelude - after that `.ghci` file is loaded, where we load right `Prelude.hs` and import it, and turn implicit prelude on - loading of package proceeds It seems to work, but fragile it seems. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10920#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10920: ghci can't load local Prelude module -------------------------------------+------------------------------------- Reporter: Yuras | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by lelf): * cc: lelf (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10920#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC