Hassan Al-Awwadi pushed to branch wip/haanss/depdir at Glasgow Haskell Compiler / GHC

Commits:

7 changed files:

Changes:

  • compiler/GHC/HsToCore/Usage.hs
    ... ... @@ -31,7 +31,6 @@ import GHC.Unit.External
    31 31
     import GHC.Unit.Module.Imported
    
    32 32
     import GHC.Unit.Module.ModIface
    
    33 33
     import GHC.Unit.Module.Deps
    
    34
    -import GHC.Unit.Finder(getDirHash)
    
    35 34
     
    
    36 35
     import GHC.Data.Maybe
    
    37 36
     import GHC.Data.FastString
    
    ... ... @@ -49,8 +48,6 @@ import GHC.Types.Unique.DFM
    49 48
     import GHC.Driver.Plugins
    
    50 49
     import qualified GHC.Unit.Home.Graph as HUG
    
    51 50
     
    
    52
    -import qualified System.Directory as SD
    
    53
    -
    
    54 51
     {- Note [Module self-dependency]
    
    55 52
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    56 53
     GHC.Rename.Names.calculateAvails asserts the invariant that a module must not occur in
    

  • compiler/GHC/Iface/Recomp.hs
    ... ... @@ -816,6 +816,7 @@ checkModUsage fc UsageFile{ usg_file_path = file,
    816 816
        handler = if debugIsOn
    
    817 817
           then \e -> pprTrace "UsageFile" (text (show e)) $ return recomp
    
    818 818
           else \_ -> return recomp -- if we can't find the file, just recompile, don't fail
    
    819
    +
    
    819 820
     checkModUsage fc UsageDirectory{ usg_dir_path = dir,
    
    820 821
                                      usg_dir_hash = old_hash,
    
    821 822
                                      usg_dir_label = mlabel } =
    
    ... ... @@ -829,7 +830,7 @@ checkModUsage fc UsageDirectory{ usg_dir_path = dir,
    829 830
        reason  = DirChanged $ unpackFS dir
    
    830 831
        recomp  = needsRecompileBecause $ fromMaybe reason $ fmap CustomReason mlabel
    
    831 832
        handler = if debugIsOn
    
    832
    -      then \e -> pprTrace "UsageDir" (text (show e)) $ return recomp
    
    833
    +      then \e -> pprTrace "UsageDirectory" (text (show e)) $ return recomp
    
    833 834
           else \_ -> return recomp -- if we can't find the dir, just recompile, don't fail
    
    834 835
     
    
    835 836
     -- | We are importing a module whose exports have changed.
    

  • compiler/GHC/Iface/Recomp/Types.hs
    ... ... @@ -140,6 +140,10 @@ pprUsage usage@UsageFile{}
    140 140
       = hsep [text "addDependentFile",
    
    141 141
               doubleQuotes (ftext (usg_file_path usage)),
    
    142 142
               ppr (usg_file_hash usage)]
    
    143
    +pprUsage usage@UsageDirectory{}
    
    144
    +  = hsep [text "AddDependentDirectory",
    
    145
    +          doubleQuotes (ftext (usg_dir_path usage)),
    
    146
    +          ppr (usg_dir_hash usage)]
    
    143 147
     pprUsage usage@UsageMergedRequirement{}
    
    144 148
       = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)]
    
    145 149
     pprUsage usage@UsageHomeModuleInterface{}
    

  • compiler/GHC/Unit/Module/Deps.hs
    ... ... @@ -490,7 +490,7 @@ instance Binary Usage where
    490 490
                 dp    <- get bh
    
    491 491
                 hash  <- get bh
    
    492 492
                 label <- get bh
    
    493
    -            return UsageDirectory { usg_dir_path = fp, usg_dir_hash = hash, usg_dir_label = label }
    
    493
    +            return UsageDirectory { usg_dir_path = dp, usg_dir_hash = hash, usg_dir_label = label }
    
    494 494
     
    
    495 495
               i -> error ("Binary.get(Usage): " ++ show i)
    
    496 496
     
    

  • testsuite/tests/interface-stability/base-exports.stdout
    ... ... @@ -7087,7 +7087,6 @@ module GHC.Fingerprint where
    7087 7087
       fingerprintFingerprints :: [Fingerprint] -> Fingerprint
    
    7088 7088
       fingerprintString :: GHC.Internal.Base.String -> Fingerprint
    
    7089 7089
       getFileHash :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint
    
    7090
    -  getDirHash  :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint
    
    7091 7090
     
    
    7092 7091
     module GHC.Fingerprint.Type where
    
    7093 7092
       -- Safety: Safe
    

  • testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
    ... ... @@ -7059,7 +7059,6 @@ module GHC.Fingerprint where
    7059 7059
       fingerprintFingerprints :: [Fingerprint] -> Fingerprint
    
    7060 7060
       fingerprintString :: GHC.Internal.Base.String -> Fingerprint
    
    7061 7061
       getFileHash :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint
    
    7062
    -  getDirHash   :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint
    
    7063 7062
     
    
    7064 7063
     module GHC.Fingerprint.Type where
    
    7065 7064
       -- Safety: Safe
    

  • testsuite/tests/interface-stability/base-exports.stdout-mingw32
    ... ... @@ -7230,7 +7230,6 @@ module GHC.Fingerprint where
    7230 7230
       fingerprintFingerprints :: [Fingerprint] -> Fingerprint
    
    7231 7231
       fingerprintString :: GHC.Internal.Base.String -> Fingerprint
    
    7232 7232
       getFileHash :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint
    
    7233
    -  getDirHash  :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint
    
    7234 7233
     
    
    7235 7234
     module GHC.Fingerprint.Type where
    
    7236 7235
       -- Safety: Safe