Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

7 changed files:

Changes:

  • compiler/GHC/Driver/Backpack.hs
    ... ... @@ -789,8 +789,8 @@ summariseRequirement pn mod_name = do
    789 789
     
    
    790 790
         env <- getBkpEnv
    
    791 791
         src_hash <- liftIO $ getFileHash (bkp_filename env)
    
    792
    -    hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
    
    793
    -    hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)
    
    792
    +    hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file_ospath location)
    
    793
    +    hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file_ospath location)
    
    794 794
         let loc = srcLocSpan (mkSrcLoc (mkFastString (bkp_filename env)) 1 1)
    
    795 795
     
    
    796 796
         let fc = hsc_FC hsc_env
    
    ... ... @@ -875,8 +875,8 @@ hsModuleToModSummary home_keys pn hsc_src modname
    875 875
                                     HsSrcFile  -> os "hs")
    
    876 876
                                  hsc_src
    
    877 877
         -- This duplicates a pile of logic in GHC.Driver.Make
    
    878
    -    hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
    
    879
    -    hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)
    
    878
    +    hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file_ospath location)
    
    879
    +    hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file_ospath location)
    
    880 880
     
    
    881 881
         -- Also copied from 'getImports'
    
    882 882
         let (src_idecls, ord_idecls) = partition ((== IsBoot) . ideclSource . unLoc) imps
    

  • compiler/GHC/Driver/Downsweep.hs
    ... ... @@ -1265,7 +1265,7 @@ checkSummaryHash
    1265 1265
       | ms_hs_hash old_summary == src_hash &&
    
    1266 1266
           not (gopt Opt_ForceRecomp (hsc_dflags hsc_env)) = do
    
    1267 1267
                -- update the object-file timestamp
    
    1268
    -           obj_timestamp <- modificationTimeIfExists (ml_obj_file location)
    
    1268
    +           obj_timestamp <- modificationTimeIfExists (ml_obj_file_ospath location)
    
    1269 1269
     
    
    1270 1270
                -- We have to repopulate the Finder's cache for file targets
    
    1271 1271
                -- because the file might not even be on the regular search path
    
    ... ... @@ -1277,8 +1277,8 @@ checkSummaryHash
    1277 1277
                    hsc_src = ms_hsc_src old_summary
    
    1278 1278
                addModuleToFinder fc mod location hsc_src
    
    1279 1279
     
    
    1280
    -           hi_timestamp <- modificationTimeIfExists (ml_hi_file location)
    
    1281
    -           hie_timestamp <- modificationTimeIfExists (ml_hie_file location)
    
    1280
    +           hi_timestamp <- modificationTimeIfExists (ml_hi_file_ospath location)
    
    1281
    +           hie_timestamp <- modificationTimeIfExists (ml_hie_file_ospath location)
    
    1282 1282
     
    
    1283 1283
                return $ Right
    
    1284 1284
                  ( old_summary
    
    ... ... @@ -1482,11 +1482,11 @@ data MakeNewModSummary
    1482 1482
     makeNewModSummary :: HscEnv -> MakeNewModSummary -> IO ModSummary
    
    1483 1483
     makeNewModSummary hsc_env MakeNewModSummary{..} = do
    
    1484 1484
       let PreprocessedImports{..} = nms_preimps
    
    1485
    -  obj_timestamp <- modificationTimeIfExists (ml_obj_file nms_location)
    
    1486
    -  dyn_obj_timestamp <- modificationTimeIfExists (ml_dyn_obj_file nms_location)
    
    1487
    -  hi_timestamp <- modificationTimeIfExists (ml_hi_file nms_location)
    
    1488
    -  hie_timestamp <- modificationTimeIfExists (ml_hie_file nms_location)
    
    1489
    -  bytecode_timestamp <- modificationTimeIfExists (ml_bytecode_file nms_location)
    
    1485
    +  obj_timestamp <- modificationTimeIfExists (ml_obj_file_ospath nms_location)
    
    1486
    +  dyn_obj_timestamp <- modificationTimeIfExists (ml_dyn_obj_file_ospath nms_location)
    
    1487
    +  hi_timestamp <- modificationTimeIfExists (ml_hi_file_ospath nms_location)
    
    1488
    +  hie_timestamp <- modificationTimeIfExists (ml_hie_file_ospath nms_location)
    
    1489
    +  bytecode_timestamp <- modificationTimeIfExists (ml_bytecode_file_ospath nms_location)
    
    1490 1490
       extra_sig_imports <- findExtraSigImports hsc_env nms_hsc_src pi_mod_name
    
    1491 1491
       (implicit_sigs, _inst_deps) <- implicitRequirementsShallow (hscSetActiveUnitId (moduleUnitId nms_mod) hsc_env) pi_theimps
    
    1492 1492
     
    

  • compiler/GHC/Driver/Main.hs
    ... ... @@ -1091,7 +1091,7 @@ loadIfaceByteCode hsc_env iface location type_env =
    1091 1091
           linkable $ pure $ DotGBC bco
    
    1092 1092
     
    
    1093 1093
         linkable parts = do
    
    1094
    -      if_time <- modificationTimeIfExists (ml_hi_file location)
    
    1094
    +      if_time <- modificationTimeIfExists (ml_hi_file_ospath location)
    
    1095 1095
           time <- maybe getCurrentTime pure if_time
    
    1096 1096
           return $! Linkable time (mi_module iface) parts
    
    1097 1097
     
    
    ... ... @@ -1112,7 +1112,7 @@ loadIfaceByteCodeLazy hsc_env iface location type_env =
    1112 1112
           linkable $ NE.singleton (DotGBC bco)
    
    1113 1113
     
    
    1114 1114
         linkable parts = do
    
    1115
    -      if_time <- modificationTimeIfExists (ml_hi_file location)
    
    1115
    +      if_time <- modificationTimeIfExists (ml_hi_file_ospath location)
    
    1116 1116
           time <- maybe getCurrentTime pure if_time
    
    1117 1117
           return $!Linkable time (mi_module iface) parts
    
    1118 1118
     
    
    ... ... @@ -2240,7 +2240,7 @@ generateAndWriteByteCodeLinkable hsc_env cgguts mod_location = do
    2240 2240
       -- Either, get the same time as the .gbc file if it exists, or just the current time.
    
    2241 2241
       -- It's important the time of the linkable matches the time of the .gbc file for recompilation
    
    2242 2242
       -- checking.
    
    2243
    -  bco_time <- maybe getCurrentTime pure =<< modificationTimeIfExists (ml_bytecode_file mod_location)
    
    2243
    +  bco_time <- maybe getCurrentTime pure =<< modificationTimeIfExists (ml_bytecode_file_ospath mod_location)
    
    2244 2244
       return $ mkModuleByteCodeLinkable bco_time bco_object
    
    2245 2245
     
    
    2246 2246
     mkModuleByteCode :: HscEnv -> Module -> ModLocation -> CgInteractiveGuts -> IO ModuleByteCode
    

  • compiler/GHC/Driver/Pipeline/Execute.hs
    ... ... @@ -730,17 +730,17 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do
    730 730
       -- the object file for one module.)
    
    731 731
       -- Note the nasty duplication with the same computation in compileFile above
    
    732 732
       location <- mkOneShotModLocation pipe_env dflags src_flavour mod_name
    
    733
    -  let o_file = ml_obj_file location -- The real object file
    
    734
    -      hi_file = ml_hi_file location
    
    735
    -      hie_file = ml_hie_file location
    
    736
    -      dyn_o_file = ml_dyn_obj_file location
    
    733
    +  let o_file = ml_obj_file_ospath location -- The real object file
    
    734
    +      hi_file = ml_hi_file_ospath location
    
    735
    +      hie_file = ml_hie_file_ospath location
    
    736
    +      dyn_o_file = ml_dyn_obj_file_ospath location
    
    737 737
     
    
    738 738
       src_hash <- getFileHash (basename <.> suff)
    
    739 739
       hi_date <- modificationTimeIfExists hi_file
    
    740 740
       hie_date <- modificationTimeIfExists hie_file
    
    741 741
       o_mod <- modificationTimeIfExists o_file
    
    742 742
       dyn_o_mod <- modificationTimeIfExists dyn_o_file
    
    743
    -  bytecode_date <- modificationTimeIfExists (ml_bytecode_file location)
    
    743
    +  bytecode_date <- modificationTimeIfExists (ml_bytecode_file_ospath location)
    
    744 744
     
    
    745 745
       -- Tell the finder cache about this module
    
    746 746
       mod <- do
    

  • compiler/GHC/Linker/Loader.hs
    ... ... @@ -658,8 +658,9 @@ findWholeCoreBindings hsc_env mod = do
    658 658
     
    
    659 659
     findBytecodeLinkableMaybe :: HscEnv -> Module -> ModLocation -> IO (Maybe Linkable)
    
    660 660
     findBytecodeLinkableMaybe hsc_env mod locn = do
    
    661
    -  let bytecode_fn = ml_bytecode_file locn
    
    662
    -  maybe_bytecode_time <- modificationTimeIfExists bytecode_fn
    
    661
    +  let bytecode_fn    = ml_bytecode_file locn
    
    662
    +      bytecode_fn_os = ml_bytecode_file_ospath locn
    
    663
    +  maybe_bytecode_time <- modificationTimeIfExists bytecode_fn_os
    
    663 664
       case maybe_bytecode_time of
    
    664 665
         Nothing -> return Nothing
    
    665 666
         Just bytecode_time -> do
    

  • compiler/GHC/Unit/Finder.hs
    ... ... @@ -826,7 +826,7 @@ mkStubPaths fopts mod location = do
    826 826
     findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)
    
    827 827
     findObjectLinkableMaybe mod locn
    
    828 828
        = do let obj_fn = ml_obj_file locn
    
    829
    -        maybe_obj_time <- modificationTimeIfExists obj_fn
    
    829
    +        maybe_obj_time <- modificationTimeIfExists (ml_obj_file_ospath locn)
    
    830 830
             case maybe_obj_time of
    
    831 831
               Nothing -> return Nothing
    
    832 832
               Just obj_time -> liftM Just (findObjectLinkable mod obj_fn obj_time)
    

  • compiler/GHC/Utils/Misc.hs
    ... ... @@ -137,6 +137,8 @@ import Control.Monad ( guard )
    137 137
     import Control.Monad.IO.Class ( MonadIO, liftIO )
    
    138 138
     import System.IO.Error as IO ( isDoesNotExistError )
    
    139 139
     import System.Directory ( doesDirectoryExist, getModificationTime, renameFile )
    
    140
    +import qualified System.Directory.OsPath as OsPath
    
    141
    +import System.OsPath (OsPath)
    
    140 142
     import System.FilePath
    
    141 143
     
    
    142 144
     import Data.Bifunctor   ( first, second )
    
    ... ... @@ -1248,9 +1250,9 @@ getModificationUTCTime = getModificationTime
    1248 1250
     -- --------------------------------------------------------------
    
    1249 1251
     -- check existence & modification time at the same time
    
    1250 1252
     
    
    1251
    -modificationTimeIfExists :: FilePath -> IO (Maybe UTCTime)
    
    1253
    +modificationTimeIfExists :: OsPath -> IO (Maybe UTCTime)
    
    1252 1254
     modificationTimeIfExists f =
    
    1253
    -  (do t <- getModificationUTCTime f; return (Just t))
    
    1255
    +  (do t <- OsPath.getModificationTime f; return (Just t))
    
    1254 1256
             `catchIO` \e -> if isDoesNotExistError e
    
    1255 1257
                             then return Nothing
    
    1256 1258
                             else ioError e