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

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Sun Aug 21 21:47:41 UTC 2022



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


Commits:
38607298 by Matthew Pickering at 2022-08-21T22:46:58+01:00
fixes

- - - - -


1 changed file:

- hadrian/src/Rules/ToolArgs.hs


Changes:

=====================================
hadrian/src/Rules/ToolArgs.hs
=====================================
@@ -1,7 +1,7 @@
 {-# LANGUAGE ViewPatterns #-}
 module Rules.ToolArgs(toolArgsTarget) where
 
-import qualified Rules.Generate
+import Rules.Generate
 import Development.Shake
 import Target
 import Context
@@ -61,7 +61,6 @@ multiSetup pkg_s = do
   -- Get the arguments for all the targets
   pargs <- mapM one_args tool_targets
   -- Build any other dependencies (such as generated files)
-  allDeps
   liftIO $ writeOutput (concatMap (\x -> ["-unit", x]) (map ( "@" <>) pargs))
 
   where
@@ -84,7 +83,8 @@ multiSetup pkg_s = do
       -- dependent packages will also be built.
       cd <- readContextData c
       srcs <- hsSources c
-      need srcs
+      gens <- interpretInContext c generatedDependencies
+      need (srcs ++ gens)
       let rexp m = ["-reexported-module", m]
       writeFile' (resp_file root p) (intercalate "\n" (th_hack arg_list
                                                       ++  modules cd
@@ -123,36 +123,24 @@ mkToolTarget es p = do
     -- This builds automatically generated dependencies. Not sure how to do
     -- this generically yet.
     putProgressInfo ("Computing arguments for " ++ pkgName p)
-    allDeps
-    let fake_target = target (Context stage0InTree p (if windowsHost then vanilla else dynamic) Final)
+
+    let context = Context stage0InTree p (if windowsHost then vanilla else dynamic) Final
+    let fake_target = target context
                         (Ghc ToolArgs stage0InTree) [] ["ignored"]
+    -- Generate any source files for this target
+    cd <- readContextData context
+    srcs <- hsSources context
+    gens <- interpretInContext context generatedDependencies
+
+    -- Build any necessary dependencies
+    depPkgIds <- cabalDependencies context
+    dep_confs <- mapM (\pkgId -> packageDbPath (PackageDbLoc stage0InTree Final) <&> (-/- pkgId <.> "conf")) depPkgIds
+
+    need (gens ++ srcs ++ dep_confs)
+
     arg_list <- interpret fake_target getArgs
     liftIO $ writeOutput (arg_list ++ es)
 
-allDeps :: Action ()
-allDeps = do
-   do
-    -- We can't build DLLs on Windows (yet). Actually we should only
-    -- include the dynamic way when we have a dynamic host GHC, but just
-    -- checking for Windows seems simpler for now.
-    let fake_target = target (Context stage0InTree compiler (if windowsHost then vanilla else dynamic) Final)
-                             (Ghc ToolArgs stage0InTree) [] ["ignored"]
-
-    -- need the autogenerated files so that they are precompiled
-    interpret fake_target Rules.Generate.compilerDependencies >>= need
-
-    root <- buildRoot
-    let ghc_prim = buildDir (vanillaContext stage0InTree ghcPrim)
-    let dir = buildDir (vanillaContext stage0InTree compiler)
-    need [ root -/- dir -/- "GHC" -/- "Settings" -/- "Config.hs" ]
-    need [ root -/- dir -/- "GHC" -/- "Parser.hs" ]
-    need [ root -/- dir -/- "GHC" -/- "Parser" -/- "Lexer.hs" ]
-    need [ root -/- dir -/- "GHC" -/- "Parser" -/- "HaddockLex.hs" ]
-    need [ root -/- dir -/- "GHC" -/- "Cmm" -/- "Parser.hs" ]
-    need [ root -/- dir -/- "GHC" -/- "Cmm" -/- "Lexer.hs"  ]
-
-    need [ root -/- ghc_prim -/- "GHC" -/- "PrimopWrappers.hs" ]
-
 -- This list is quite a lot like stage0packages but doesn't include
 -- critically the `exe:ghc` component as that depends on the GHC library
 -- which takes a while to compile.
@@ -190,8 +178,6 @@ toolTargets = [ binary
 -- | Create a mapping from files to which component it belongs to.
 dirMap :: Action [(FilePath, (Package, [String]))]
 dirMap = do
-  depPkgIds <- concat <$> mapM (cabalDependencies . vanillaContext stage0InTree) toolTargets
-  need =<< mapM (\pkgId -> packageDbPath (PackageDbLoc stage0InTree Final) <&> (-/- pkgId <.> "conf")) depPkgIds
   auto <- concatMapM go toolTargets
   -- Mush the ghc executable into the compiler component so the whole of ghc is not built when
   -- configuring



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/38607298f61d01f70536557a3fb1271acd48d513

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/38607298f61d01f70536557a3fb1271acd48d513
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/20220821/8843c9d5/attachment-0001.html>


More information about the ghc-commits mailing list