[commit: ghc] wip/T16197: Make sure 'haddock' package also copies resources (8765c1e)

git at git.haskell.org git at git.haskell.org
Thu Jan 17 13:59:31 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/T16197
Link       : http://ghc.haskell.org/trac/ghc/changeset/8765c1e6e6aca590a2fc252c64846890bf87f387/ghc

>---------------------------------------------------------------

commit 8765c1e6e6aca590a2fc252c64846890bf87f387
Author: Alec Theriault <alec.theriault at gmail.com>
Date:   Thu Jan 10 04:37:36 2019 -0800

    Make sure 'haddock' package also copies resources
    
    ...and does so in the lib folder of the right stage


>---------------------------------------------------------------

8765c1e6e6aca590a2fc252c64846890bf87f387
 hadrian/src/Base.hs                      | 15 ++++++++++++++-
 hadrian/src/Builder.hs                   | 12 +-----------
 hadrian/src/Rules/Documentation.hs       | 13 -------------
 hadrian/src/Rules/Generate.hs            | 14 +++++++++-----
 hadrian/src/Rules/Program.hs             |  3 +++
 hadrian/src/Settings/Builders/Haddock.hs |  8 ++++----
 6 files changed, 31 insertions(+), 34 deletions(-)

diff --git a/hadrian/src/Base.hs b/hadrian/src/Base.hs
index cb0dba0..277d614 100644
--- a/hadrian/src/Base.hs
+++ b/hadrian/src/Base.hs
@@ -24,7 +24,8 @@ module Base (
     -- * Paths
     hadrianPath, configPath, configFile, sourcePath, shakeFilesDir,
     generatedDir, generatedPath, stageBinPath, stageLibPath, templateHscPath,
-    ghcDeps, relativePackageDbPath, packageDbPath, packageDbStamp, ghcSplitPath
+    ghcDeps, haddockDeps, relativePackageDbPath, packageDbPath, packageDbStamp,
+    ghcSplitPath
     ) where
 
 import Control.Applicative
@@ -37,6 +38,7 @@ import Development.Shake hiding (parallel, unit, (*>), Normal)
 import Development.Shake.Classes
 import Development.Shake.FilePath
 import Development.Shake.Util
+import Hadrian.Oracles.DirectoryContents
 import Hadrian.Utilities
 import Hadrian.Package
 
@@ -114,6 +116,17 @@ ghcDeps stage = mapM (\f -> stageLibPath stage <&> (-/- f))
       , "platformConstants"
       , "settings" ]
 
+-- | Files the `haddock` binary depends on
+haddockDeps :: Stage -> Action [FilePath]
+haddockDeps stage = do
+    let resdir = "utils/haddock/haddock-api/resources"
+    latexResources <- directoryContents matchAll (resdir -/- "latex")
+    htmlResources  <- directoryContents matchAll (resdir -/- "html")
+
+    haddockLib <- stageLibPath stage
+    return $ [ haddockLib -/- makeRelative resdir f
+             | f <- latexResources ++ htmlResources ]
+
 -- ref: utils/hsc2hs/ghc.mk
 -- | Path to 'hsc2hs' template.
 templateHscPath :: Stage -> Action FilePath
diff --git a/hadrian/src/Builder.hs b/hadrian/src/Builder.hs
index 55dcb3c..d09af99 100644
--- a/hadrian/src/Builder.hs
+++ b/hadrian/src/Builder.hs
@@ -23,7 +23,6 @@ import Hadrian.Builder.Sphinx
 import Hadrian.Builder.Tar
 import Hadrian.Oracles.Path
 import Hadrian.Oracles.TextFile
-import Hadrian.Oracles.DirectoryContents
 import Hadrian.Utilities
 
 import Base
@@ -188,16 +187,7 @@ instance H.Builder Builder where
 
         Hsc2Hs stage -> (\p -> [p]) <$> templateHscPath stage
         Make dir  -> return [dir -/- "Makefile"]
-
-        Haddock _ -> do
-            let resdir = "utils/haddock/haddock-api/resources"
-            latexResources <- directoryContents matchAll (resdir -/- "latex")
-            htmlResources  <- directoryContents matchAll (resdir -/- "html")
-
-            haddockLib <- stageLibPath Stage1   -- Haddock is built in stage1
-            return $ [ haddockLib -/- makeRelative resdir f
-                     | f <- latexResources ++ htmlResources ]
-
+        Haddock _ -> haddockDeps Stage1  -- Haddock currently runs in Stage1
         _         -> return []
 
     -- query the builder for some information.
diff --git a/hadrian/src/Rules/Documentation.hs b/hadrian/src/Rules/Documentation.hs
index 2aa663f..954264a 100644
--- a/hadrian/src/Rules/Documentation.hs
+++ b/hadrian/src/Rules/Documentation.hs
@@ -64,8 +64,6 @@ pathPath _ = ""
 -- | Build all documentation
 documentationRules :: Rules ()
 documentationRules = do
-    haddockResources
-
     buildDocumentationArchives
     buildHtmlDocumentation
     buildManPage
@@ -109,17 +107,6 @@ buildSphinxHtml path = do
 
 ------------------------------------ Haddock -----------------------------------
 
--- | Copy resources into the @lib@ directory
-haddockResources :: Rules ()
-haddockResources = do
-    root <- buildRootRules
-    let resdir = "utils/haddock/haddock-api/resources"
-        haddockLib = root -/- "stage1/lib"    -- Haddock is built in stage1
-
-    [ haddockLib -/- "html//*", haddockLib -/- "latex//*" ] |%> \target -> do
-        let source = resdir -/- makeRelative haddockLib target
-        copyFile source target
-
 -- | Build the haddocks for GHC's libraries.
 buildLibraryDocumentation :: Rules ()
 buildLibraryDocumentation = do
diff --git a/hadrian/src/Rules/Generate.hs b/hadrian/src/Rules/Generate.hs
index e035753..9db5b19 100644
--- a/hadrian/src/Rules/Generate.hs
+++ b/hadrian/src/Rules/Generate.hs
@@ -161,6 +161,12 @@ copyRules = do
     root <- buildRootRules
     forM_ [Stage0 ..] $ \stage -> do
         let prefix = root -/- stageString stage -/- "lib"
+
+            infixl 1 <~
+            pattern <~ mdir = pattern %> \file -> do
+                dir <- mdir
+                copyFile (dir -/- makeRelative prefix file) file
+
         prefix -/- "ghc-usage.txt"     <~ return "driver"
         prefix -/- "ghci-usage.txt"    <~ return "driver"
         prefix -/- "llvm-targets"      <~ return "."
@@ -168,11 +174,9 @@ copyRules = do
         prefix -/- "platformConstants" <~ (buildRoot <&> (-/- generatedDir))
         prefix -/- "settings"          <~ return "."
         prefix -/- "template-hsc.h"    <~ return (pkgPath hsc2hs)
-  where
-    infixl 1 <~
-    pattern <~ mdir = pattern %> \file -> do
-        dir <- mdir
-        copyFile (dir -/- takeFileName file) file
+
+        prefix -/- "html//*"           <~ return "utils/haddock/haddock-api/resources"
+        prefix -/- "latex//*"          <~ return "utils/haddock/haddock-api/resources"
 
 generateRules :: Rules ()
 generateRules = do
diff --git a/hadrian/src/Rules/Program.hs b/hadrian/src/Rules/Program.hs
index 9d8b6d0..c9df6f5 100644
--- a/hadrian/src/Rules/Program.hs
+++ b/hadrian/src/Rules/Program.hs
@@ -71,6 +71,9 @@ buildProgram bin ctx@(Context{..}) rs = do
     -- @llvm-targets@, @ghc-usage.txt@, @ghci-usage.txt@,
     -- @llvm-passes at .
     need =<< ghcDeps stage
+  when (package == haddock) $ do
+    -- Haddock has a resource folder
+    need =<< haddockDeps stage
 
   cross <- flag CrossCompiling
   -- For cross compiler, copy @stage0/bin/<pgm>@ to @stage1/bin/@.
diff --git a/hadrian/src/Settings/Builders/Haddock.hs b/hadrian/src/Settings/Builders/Haddock.hs
index 92ac714..65c7031 100644
--- a/hadrian/src/Settings/Builders/Haddock.hs
+++ b/hadrian/src/Settings/Builders/Haddock.hs
@@ -20,8 +20,8 @@ haddockBuilderArgs = mconcat
         inputs <- getInputs
         root   <- getBuildRoot
         mconcat
-            [ arg $ "-B" ++ root -/- "stage1" -/- "lib"
-            , arg $ "--lib=" ++ root -/- "stage1" -/- "lib"
+            [ arg $ "-B" ++ root -/- stageString Stage1 -/- "lib"
+            , arg $ "--lib=" ++ root -/- stageString Stage1 -/- "lib"
             , arg "--gen-index"
             , arg "--gen-contents"
             , arg "-o", arg $ takeDirectory output
@@ -45,8 +45,8 @@ haddockBuilderArgs = mconcat
         ghcOpts  <- haddockGhcArgs
         mconcat
             [ arg "--verbosity=0"
-            , arg $ "-B" ++ root -/- "stage1" -/- "lib"
-            , arg $ "--lib=" ++ root -/- "stage1" -/- "lib"
+            , arg $ "-B" ++ root -/- stageString Stage1 -/- "lib"
+            , arg $ "--lib=" ++ root -/- stageString Stage1 -/- "lib"
             , arg $ "--odir=" ++ takeDirectory output
             , arg "--no-tmp-comp-dir"
             , arg $ "--dump-interface=" ++ output



More information about the ghc-commits mailing list