[GHC] #15369: GHCi doesn't honor ':set +c' when loading, for a second time, a file that has .hi/.o

GHC ghc-devs at haskell.org
Thu Jul 12 15:27:47 UTC 2018


#15369: GHCi doesn't honor ':set +c' when loading, for a second time, a file that
has .hi/.o
-------------------------------------+-------------------------------------
           Reporter:  dramforever    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.4.3
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 If a file `foo.hs` is compiled and has `foo.hi` and `foo.o` lying around,
 then the ''second time'' `foo.hs` is loaded in GHCi (with `set +c` set),
 even with `:load *foo.hs` to force interpretation, the file loads fine but
 the type information is not collected, as if `:set +c` wasn't in effect.

 This means that commands like `:type-at` and `:all-types` work as if they
 had the old file.

 I expect that given `:set +c`, a successful `:load *foo.hs` would always
 collect the new type information for `foo.hs`.

 == Steps to reproduce

 The contents of `setc.hs` is the following, although it's pretty surely
 irrelevant.

 {{{#!hs
 module SetC where
 }}}

 The following is a GHCi session showing the problem (my comments are
 marked with `--`).

 {{{
 GHCi, version 8.4.3: http://www.haskell.org/ghc/  :? for help
 Prelude> :set +c

 -- dir /b is basically ls on Windows
 Prelude> :! dir /b setc*
 setc.hs

 -- When I load a file multiple times it works fine
 Prelude> :load *setc.hs
 [1 of 1] Compiling SetC             ( setc.hs, interpreted )
 Ok, one module loaded.
 Collecting type info for 1 module(s) ...    -- Collected
 *SetC> :load *setc.hs
 [1 of 1] Compiling SetC             ( setc.hs, interpreted )
 Ok, one module loaded.
 Collecting type info for 1 module(s) ...    -- Collected

 -- But if I compile it
 *SetC> :! ghc -c setc.hs
 *SetC> :! dir /b setc*
 setc.hi
 setc.hs
 setc.o

 -- The first time the type info is collected
 *SetC> :load *setc.hs
 [1 of 1] Compiling SetC             ( setc.hs, interpreted )
 Ok, one module loaded.
 Collecting type info for 1 module(s) ...    -- Collected

 -- But then it is no longer collected
 *SetC> :load *setc.hs
 [1 of 1] Compiling SetC             ( setc.hs, interpreted )
 Ok, one module loaded.                      -- NOT collected!
 *SetC>
 }}}

 Then if I change `setc.hs` to add some expressions:

 {{{#!hs
 module SetC where

 x :: Int
 x = 1
 }}}

 {{{
 *SetC> :load *setc.hs
 [1 of 1] Compiling SetC             ( setc.hs, interpreted )
 Ok, one module loaded.                      -- NOT collected!

 -- The new definition is loaded fine
 *SetC> x
 1

 -- But the type information is not there (no output!)
 *SetC> :all-types
 *SetC>

 -- Then if I delete the compiled .hi and .o files
 *SetC> :! del setc.hi setc.o

 -- ... and load again, :all-types suddenly works
 *SetC> :load *setc.hs
 [1 of 1] Compiling SetC             ( setc.hs, interpreted )
 Ok, one module loaded.
 Collecting type info for 1 module(s) ...    -- Collected
 *SetC> :all-types
 setc.hs:(4,1)-(4,2): GHC.Types.Int
 setc.hs:(4,5)-(4,6): GHC.Types.Int
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15369>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list