[Git][ghc/ghc][wip/inplace-final] clean

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Mon Aug 22 14:52:07 UTC 2022



Matthew Pickering pushed to branch wip/inplace-final at Glasgow Haskell Compiler / GHC


Commits:
54395443 by Matthew Pickering at 2022-08-22T15:52:00+01:00
clean

- - - - -


4 changed files:

- hadrian/src/Builder.hs
- hadrian/src/Rules/Library.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Settings/Builders/GhcPkg.hs


Changes:

=====================================
hadrian/src/Builder.hs
=====================================
@@ -103,7 +103,7 @@ instance NFData   ConfigurationInfo
 -- TODO: Do we really need all these modes? Why do we need 'Dependencies'? We
 -- can extract dependencies using the Cabal library.
 -- | 'GhcPkg' can initialise a package database and register packages in it.
-data GhcPkgMode = Init         -- ^ Initialise an empty package database
+data GhcPkgMode = Recache      -- ^ Recache a package database
                 | Copy         -- ^ Copy a package from one database to another.
                 | Dependencies -- ^ Compute package dependencies.
                 | Unregister   -- ^ Unregister a package.


=====================================
hadrian/src/Rules/Library.hs
=====================================
@@ -17,7 +17,6 @@ import Target
 import Utilities
 import Data.Time.Clock
 import Rules.Generate (generatedDependencies)
-import Hadrian.Oracles.Cabal (readPackageData)
 import Oracles.Flag
 
 
@@ -111,20 +110,15 @@ buildGhciLibO root ghcilibPath = do
 
 buildPackage :: FilePath -> FilePath -> Action ()
 buildPackage root fp = do
-  l@(BuildPath _ stage _ (PkgStamp _ _ way)) <- parsePath (parseStampPath root) "<.stamp parser>" fp
+  l@(BuildPath _ _ _ (PkgStamp _ _ way)) <- parsePath (parseStampPath root) "<.stamp parser>" fp
   let ctx = stampContext l
   srcs <- hsSources ctx
   gens <- interpretInContext ctx generatedDependencies
 
-  depPkgs <- packageDependencies <$> readPackageData (package ctx)
-  -- Stage packages are those we have in this stage.
-  stagePkgs <- stagePackages stage
+  lib_targets <- libraryTargets True ctx
 
-  need (srcs ++ gens)
+  need (srcs ++ gens ++ lib_targets)
 
---  ways <- interpretInContext context (getLibraryWays <> if package == rts then getRtsWays else mempty)
-  need =<< libraryTargets True ctx
-  --unless (null srcs) (build $ target ctx (Ghc (CompileHs GhcMake) stage) srcs [])
   time <- liftIO $ getCurrentTime
   liftIO $ writeFile fp (show time)
   ways <- interpretInContext ctx getLibraryWays


=====================================
hadrian/src/Rules/Register.hs
=====================================
@@ -95,7 +95,7 @@ registerPackageRules rs stage iplace = do
         -- a package gets registered but there's not a package.cache file (which
         -- leads to errors in GHC).
         buildWithResources rs $
-            target (Context stage compiler vanilla iplace) (GhcPkg Init stage) [] []
+            target (Context stage compiler vanilla iplace) (GhcPkg Recache stage) [] []
         writeFileLines stamp []
 
     -- Register a package.
@@ -152,7 +152,7 @@ buildConfFinal rs context at Context {..} _conf = do
     Cabal.copyPackage context
     Cabal.registerPackage context
     buildWithResources rs $
-      target context (GhcPkg Init stage) [] []
+      target context (GhcPkg Recache stage) [] []
 
     -- We declare that this rule also produces files matching:
     --   - <root>/stage<N>/lib/<arch>-<os>-ghc-<version>/*libHS<pkgid>*
@@ -175,10 +175,6 @@ buildConfInplace rs context at Context {..} _conf = do
     ensureConfigured context
     need =<< mapM (\pkgId -> packageDbPath (PackageDbLoc stage Inplace) <&> (-/- pkgId <.> "conf")) depPkgIds
 
-   -- ways <- interpretInContext context (getLibraryWays <> if package == rts then getRtsWays else mempty)
-   -- need . traceShowId =<< mapM pkgStampFile [ context { way = w } | w <- Set.toList ways ]
-
-    -- We might need some package-db resource to limit read/write, see packageRules.
     path <- buildPath context
 
     -- Special package cases (these should ideally be rolled into Cabal).
@@ -198,31 +194,12 @@ buildConfInplace rs context at Context {..} _conf = do
         when (bignum == "gmp") $
             need [path -/- "include/ghc-gmp.h"]
 
-    -- Copy and register the package.
---    Cabal.copyPackage context
+    -- Write an "inplace" package conf which points into the build directories
+    -- for finding the build products
     Cabal.writeFakePkgConf context
     conf <- pkgInplaceConfig context
---    runBuilder (GhcPkg Update stage) [] [conf] []
-
     buildWithResources rs $
       target context (GhcPkg Update stage) [conf] []
---    Cabal.
-
-    -- We declare that this rule also produces files matching:
-    --   - <root>/stage<N>/lib/<arch>-<os>-ghc-<version>/*libHS<pkgid>*
-    --     (for .so files, Cabal's registration mechanism places them there)
-    --   - <root>/stage<N>/lib/<arch>-<os>-ghc-<version>/<pkgid>/**
-    --     (for interface files, static libs, ghci libs, includes, ...)
-    --
-    -- so that if any change ends up modifying a library (but not its .conf
-    -- file), we still rebuild things that depend on it.
-    dir <- (-/-) <$> libPath context <*> distDir stage
-    pkgid <- pkgIdentifier package
-    files <- liftIO $
-      (++) <$> getDirectoryFilesIO "." [dir -/- "*libHS"++pkgid++"*"]
-           <*> getDirectoryFilesIO "." [dir -/- pkgid -/- "**"]
-    produces files
-
 
 
 copyConf :: [(Resource, Int)] -> Context -> FilePath -> Action ()


=====================================
hadrian/src/Settings/Builders/GhcPkg.hs
=====================================
@@ -4,7 +4,7 @@ import Settings.Builders.Common
 
 ghcPkgBuilderArgs :: Args
 ghcPkgBuilderArgs = mconcat
-    [ builder (GhcPkg Init) ? do
+    [ builder (GhcPkg Recache) ? do
         loc <- getPackageDbLoc
         pkgDb     <- expr $ packageDbPath loc
         -- Confusingly calls recache rather than init because shake "creates"



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5439544354ef7240174e473b97771ae1efefa6a5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5439544354ef7240174e473b97771ae1efefa6a5
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20220822/0ed402e5/attachment-0001.html>


More information about the ghc-commits mailing list