[Git][ghc/ghc][wip/haanss/depdir] 2 commits: got letter wrong

Hassan Al-Awwadi pushed to branch wip/haanss/depdir at Glasgow Haskell Compiler / GHC Commits: 582bc274 by Hassan Al-Awwadi at 2025-07-05T13:53:03+02:00 got letter wrong - - - - - 5a6525bb by Hassan Al-Awwadi at 2025-07-05T14:11:54+02:00 more missing cases for UsageDirectory added and some clean up - - - - - 7 changed files: - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Unit/Module/Deps.hs - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 Changes: ===================================== compiler/GHC/HsToCore/Usage.hs ===================================== @@ -31,7 +31,6 @@ import GHC.Unit.External import GHC.Unit.Module.Imported import GHC.Unit.Module.ModIface import GHC.Unit.Module.Deps -import GHC.Unit.Finder(getDirHash) import GHC.Data.Maybe import GHC.Data.FastString @@ -49,8 +48,6 @@ import GHC.Types.Unique.DFM import GHC.Driver.Plugins import qualified GHC.Unit.Home.Graph as HUG -import qualified System.Directory as SD - {- Note [Module self-dependency] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 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, handler = if debugIsOn then \e -> pprTrace "UsageFile" (text (show e)) $ return recomp else \_ -> return recomp -- if we can't find the file, just recompile, don't fail + checkModUsage fc UsageDirectory{ usg_dir_path = dir, usg_dir_hash = old_hash, usg_dir_label = mlabel } = @@ -829,7 +830,7 @@ checkModUsage fc UsageDirectory{ usg_dir_path = dir, reason = DirChanged $ unpackFS dir recomp = needsRecompileBecause $ fromMaybe reason $ fmap CustomReason mlabel handler = if debugIsOn - then \e -> pprTrace "UsageDir" (text (show e)) $ return recomp + then \e -> pprTrace "UsageDirectory" (text (show e)) $ return recomp else \_ -> return recomp -- if we can't find the dir, just recompile, don't fail -- | We are importing a module whose exports have changed. ===================================== compiler/GHC/Iface/Recomp/Types.hs ===================================== @@ -140,6 +140,10 @@ pprUsage usage@UsageFile{} = hsep [text "addDependentFile", doubleQuotes (ftext (usg_file_path usage)), ppr (usg_file_hash usage)] +pprUsage usage@UsageDirectory{} + = hsep [text "AddDependentDirectory", + doubleQuotes (ftext (usg_dir_path usage)), + ppr (usg_dir_hash usage)] pprUsage usage@UsageMergedRequirement{} = hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)] pprUsage usage@UsageHomeModuleInterface{} ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -490,7 +490,7 @@ instance Binary Usage where dp <- get bh hash <- get bh label <- get bh - return UsageDirectory { usg_dir_path = fp, usg_dir_hash = hash, usg_dir_label = label } + return UsageDirectory { usg_dir_path = dp, usg_dir_hash = hash, usg_dir_label = label } i -> error ("Binary.get(Usage): " ++ show i) ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -7087,7 +7087,6 @@ module GHC.Fingerprint where fingerprintFingerprints :: [Fingerprint] -> Fingerprint fingerprintString :: GHC.Internal.Base.String -> Fingerprint getFileHash :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint - getDirHash :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint module GHC.Fingerprint.Type where -- Safety: Safe ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -7059,7 +7059,6 @@ module GHC.Fingerprint where fingerprintFingerprints :: [Fingerprint] -> Fingerprint fingerprintString :: GHC.Internal.Base.String -> Fingerprint getFileHash :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint - getDirHash :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint module GHC.Fingerprint.Type where -- Safety: Safe ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -7230,7 +7230,6 @@ module GHC.Fingerprint where fingerprintFingerprints :: [Fingerprint] -> Fingerprint fingerprintString :: GHC.Internal.Base.String -> Fingerprint getFileHash :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint - getDirHash :: GHC.Internal.IO.FilePath -> GHC.Internal.Types.IO Fingerprint module GHC.Fingerprint.Type where -- Safety: Safe View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e4016a66aa751eeb863b6a01680647e... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e4016a66aa751eeb863b6a01680647e... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Hassan Al-Awwadi (@hassan.awwadi)