[GHC] #9718: Avoid TidyPgm predicting what CorePrep will do

GHC ghc-devs at haskell.org
Thu Dec 6 05:44:55 UTC 2018


#9718: Avoid TidyPgm predicting what CorePrep will do
-------------------------------------+-------------------------------------
        Reporter:  simonpj           |                Owner:  (none)
            Type:  task              |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  7.8.3
      Resolution:                    |             Keywords:  CodeGen, CAFs
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 osa1):

 OK so it turns out I made a mistake in my testing and end up not testing
 anything. I submitted Phab:D5416 to fix a confusing variable naming which
 is
 what confused me. Currently I'm stuck with a weird error caused when I add
 one
 more `hscWriteIface` call after code generation, without changing the
 interface
 file (so I'm just writing the same interface file again, later in
 compilation).
 The diff to reproduce is:

 {{{
 diff --git a/compiler/main/DriverPipeline.hs
 b/compiler/main/DriverPipeline.hs
 index a9e486c94a..c614d7f102 100644
 --- a/compiler/main/DriverPipeline.hs
 +++ b/compiler/main/DriverPipeline.hs
 @@ -193,7 +193,7 @@ compileOne' m_tc_result mHscMessage
              o_time <- getModificationUTCTime object_filename
              let linkable = LM o_time this_mod [DotO object_filename]
              return hmi0 { hm_linkable = Just linkable }
 -        (HscRecomp cgguts summary, HscInterpreted) -> do
 +        (HscRecomp cgguts summary _iface, HscInterpreted) -> do
              (hasStub, comp_bc, spt_entries) <-
                  hscInteractive hsc_env cgguts summary

 @@ -214,14 +214,14 @@ compileOne' m_tc_result mHscMessage
              let linkable = LM unlinked_time (ms_mod summary)
                             (hs_unlinked ++ stub_o)
              return hmi0 { hm_linkable = Just linkable }
 -        (HscRecomp cgguts summary, _) -> do
 +        (HscRecomp cgguts summary iface, _) -> do
              output_fn <- getOutputFilename next_phase
                              (Temporary TFL_CurrentModule)
                              basename dflags next_phase (Just location)
              -- We're in --make mode: finish the compilation pipeline.
              _ <- runPipeline StopLn hsc_env
                                (output_fn,
 -                               Just (HscOut src_flavour mod_name
 (HscRecomp cgguts summary)))
 +                               Just (HscOut src_flavour mod_name
 (HscRecomp cgguts summary iface)))
                                (Just basename)
                                Persistent
                                (Just location)
 @@ -1104,13 +1104,13 @@ runPhase (HscOut src_flavour mod_name result) _
 dflags = do
                         basename = dropExtension input_fn
                     liftIO $ compileEmptyStub dflags hsc_env' basename
 location mod_name
                     return (RealPhase StopLn, o_file)
 -            HscRecomp cgguts mod_summary
 +            HscRecomp cgguts mod_summary iface
                -> do output_fn <- phaseOutputFilename next_phase

                      PipeState{hsc_env=hsc_env'} <- getPipeState

                      (outputFilename, mStub, foreign_files) <- liftIO $
 -                      hscGenHardCode hsc_env' cgguts mod_summary
 output_fn
 +                      hscGenHardCode hsc_env' cgguts mod_summary iface
 output_fn
                      stub_o <- liftIO (mapM (compileStub hsc_env') mStub)
                      foreign_os <- liftIO $
                        mapM (uncurry (compileForeign hsc_env'))
 foreign_files
 diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
 index d7cebd00fc..198865d6e0 100644
 --- a/compiler/main/HscMain.hs
 +++ b/compiler/main/HscMain.hs
 @@ -763,7 +763,7 @@ finish summary tc_result mb_old_hash = do
              desugared_guts <- hscSimplify' plugins desugared_guts0
              (iface, changed, details, cgguts) <-
                liftIO $ hscNormalIface hsc_env desugared_guts mb_old_hash
 -            return (iface, changed, details, HscRecomp cgguts summary)
 +            return (iface, changed, details, HscRecomp cgguts summary
 iface)
        else mk_simple_iface
    liftIO $ hscMaybeWriteIface dflags iface changed summary
    return
 @@ -1292,10 +1292,10 @@ hscWriteIface dflags iface no_change mod_summary =
 do
          writeIfaceFile dynDflags dynIfaceFile' iface

  -- | Compile to hard-code.
 -hscGenHardCode :: HscEnv -> CgGuts -> ModSummary -> FilePath
 +hscGenHardCode :: HscEnv -> CgGuts -> ModSummary -> ModIface -> FilePath
                 -> IO (FilePath, Maybe FilePath, [(ForeignSrcLang,
 FilePath)])
                 -- ^ @Just f@ <=> _stub.c is f
 -hscGenHardCode hsc_env cgguts mod_summary output_filename = do
 +hscGenHardCode hsc_env cgguts mod_summary iface output_filename = do
          let CgGuts{ -- This is the last use of the ModGuts in a
 compilation.
                      -- From now on, we just use the bits we need.
                      cg_module   = this_mod,
 @@ -1327,6 +1327,11 @@ hscGenHardCode hsc_env cgguts mod_summary
 output_filename = do
              prof_init = profilingInitCode this_mod cost_centre_info
              foreign_stubs = foreign_stubs0 `appendStubC` prof_init

 +
 +        ------ Overwrite iface file with new info ------------
 +        -- Generating iface again
 +        hscWriteIface dflags iface False mod_summary
 +
          ------------------  Code generation ------------------

          -- The back-end is streamed: each top-level function goes
 diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs
 index d57d69bda6..15c7b1fb03 100644
 --- a/compiler/main/HscTypes.hs
 +++ b/compiler/main/HscTypes.hs
 @@ -222,7 +222,7 @@ data HscStatus
      | HscUpToDate
      | HscUpdateBoot
      | HscUpdateSig
 -    | HscRecomp CgGuts ModSummary
 +    | HscRecomp CgGuts ModSummary !ModIface

  --
 -----------------------------------------------------------------------------
  -- The Hsc monad: Passing an environment and warning state
 }}}

 It looks large but all I'm doing is passing the `ModIface` to the code
 generator, and overwriting the interface file (without changing anything)
 after
 STG generation. If I build GHC with this patch I get weird errors like:

 {{{
 "inplace/bin/ghc-stage1" -hisuf hi -osuf  o -hcsuf hc -static  -O0 -H64m
 -Wall      -this-unit-id ghc-prim-0.5.3 -hide-all-packages -i -ilibraries
 /ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries/ghc-prim
 /dist-install/build -ilibraries/ghc-prim/dist-install/build/./autogen
 -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/.
 -optP-include -optPlibraries/ghc-prim/dist-
 install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-
 prim -XHaskell2010 -O  -no-user-package-db -rtsopts  -Wno-trustworthy-safe
 -Wno-deprecated-flags     -Wnoncanonical-monad-instances  -odir libraries
 /ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist-install/build
 -stubdir libraries/ghc-prim/dist-install/build   -dynamic-too -c libraries
 /ghc-prim/./GHC/CString.hs -o libraries/ghc-prim/dist-
 install/build/GHC/CString.o -dyno libraries/ghc-prim/dist-
 install/build/GHC/CString.dyn_o

 libraries/ghc-prim/GHC/CString.hs:23:1: error:
     Bad interface file: libraries/ghc-prim/dist-install/build/GHC/Types.hi
         mismatched interface file ways (wanted "", got "dyn")
    |
 23 | import GHC.Types
    | ^^^^^^^^^^^^^^^^
 }}}

 I also tried writing the interface file _twice_ when we write it for the
 first
 time, just to make sure this isn't because we see a file and take a
 different
 code path and break things etc. but that's not the case, it works fine. So
 somehow if I overwrite it right after writing it, it's fine. But if I
 overwrite
 it later in compilation (after STG generation) things break.

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


More information about the ghc-tickets mailing list