[GHC] #14994: ghc api: `load LoadAllTargets` is not idempotent

GHC ghc-devs at haskell.org
Mon Apr 2 17:28:17 UTC 2018


#14994: ghc api: `load LoadAllTargets` is not idempotent
-------------------------------------+-------------------------------------
           Reporter:  int-e          |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  GHC API        |           Version:  8.4.1
           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:
-------------------------------------+-------------------------------------
 While trying to adapt `hint` for ghc 8.4.1, I've encountered the following
 phenomenon where an extra `load LoadAllTargets` line causes errors.

 {{{#!hs
 -- warning: the code below creates files A.hs and B.hs in the current
 working directory
 import System.Directory
 import Control.Monad.IO.Class
 import GHCi.RemoteTypes

 import GHC.Paths -- cf. the ghc-paths package
 import Unsafe.Coerce

 main = do
     writeFile "A.hs" "module Ahidden(a) where { a :: Int; a = 42 }"
     let mod_nameA = mkModuleName "Ahidden"
         mod_targetA = Target (TargetFile "A.hs" Nothing) False Nothing

     runGhc (Just libdir) $ do
         -- setup
         df0 <- getSessionDynFlags
         (df1, _, _) <- parseDynamicFlags df0 []
         setSessionDynFlags df1{
             ghcMode = CompManager,
             hscTarget = HscInterpreted,
             ghcLink = LinkInMemory,
             verbosity = 0
         }

         -- context : *X
         setTargets [mod_targetA]
         load LoadAllTargets
         load LoadAllTargets -- this line causes the next line to fail
         setContext [IIModule mod_nameA]
 -- error:
 --   ...: Could not find module ‘Ahidden’
 --   Use -v to see a list of the files searched for.
         runIOExpr "print a :: IO ()"

 runIOExpr e = do
     HValue h <- compileExpr e
     liftIO (unsafeCoerce h :: IO ())
 }}}

 This code works with ghc 8.2. The new behavior probably originates in
 1893ba12fe1fa2ade35a62c336594afcd569736e, which adds flushing of the
 finder cache (main/Finder.hs) for every dependency analysis; my guess is
 that this is where the connection between the module name `Ahidden` and
 the file `A.hs` used be tracked.

 http://lpaste.net/364298 is a less artificial example of the same
 behavior.

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


More information about the ghc-tickets mailing list