[commit: ghc] wip/nfs-locking: Fix documentation rules (#324) (13023bc)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 01:19:44 UTC 2017


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

On branch  : wip/nfs-locking
Link       : http://ghc.haskell.org/trac/ghc/changeset/13023bc3e13dcd003efbf00a83a7ab780c2727c3/ghc

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

commit 13023bc3e13dcd003efbf00a83a7ab780c2727c3
Author: Zhen Zhang <izgzhen at gmail.com>
Date:   Sun Jul 9 18:21:31 2017 +0800

    Fix documentation rules (#324)


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

13023bc3e13dcd003efbf00a83a7ab780c2727c3
 src/Rules/Documentation.hs | 17 ++++++++++-------
 src/Rules/Install.hs       | 14 ++++++++++++++
 src/Rules/Wrappers.hs      | 12 ++++++++++--
 3 files changed, 34 insertions(+), 9 deletions(-)

diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs
index cf54e0a..5ee6818 100644
--- a/src/Rules/Documentation.hs
+++ b/src/Rules/Documentation.hs
@@ -7,11 +7,14 @@ import Flavour
 import GHC
 import Oracles.ModuleFiles
 import Oracles.PackageData
+import Oracles.Path (getTopDirectory)
 import Settings
 import Settings.Path
 import Target
 import Util
 
+import qualified System.Directory as IO
+
 haddockHtmlLib :: FilePath
 haddockHtmlLib = "inplace/lib/html/haddock-util.js"
 
@@ -31,13 +34,6 @@ buildPackageDocumentation context at Context {..} =
                            , depPkg /= rts ]
             need $ srcs ++ haddocks ++ [haddockHtmlLib]
 
-            -- HsColour sources
-            -- TODO: what is the output of GhcCabalHsColour?
-            whenM (isSpecified HsColour) $ do
-                pkgConf <- pkgConfFile context
-                need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf
-                build $ Target context GhcCabalHsColour [cabalFile] []
-
             -- Build Haddock documentation
             -- TODO: pass the correct way from Rules via Context
             let haddockWay = if dynamicGhcPrograms flavour then dynamic else vanilla
@@ -47,6 +43,13 @@ buildPackageDocumentation context at Context {..} =
             let dir = takeDirectory haddockHtmlLib
             liftIO $ removeFiles dir ["//*"]
             copyDirectory "utils/haddock/haddock-api/resources/html" dir
+  where
+    excluded = Or
+        [ Test "//haddock-prologue.txt"
+        , Test "//package-data.mk"
+        , Test "//setup-config"
+        , Test "//inplace-pkg-config"
+        , Test "//build" ]
 
 -- # Make the haddocking depend on the library .a file, to ensure
 -- # that we wait until the library is fully built before we haddock it
diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs
index 4c91316..553f8d1 100644
--- a/src/Rules/Install.hs
+++ b/src/Rules/Install.hs
@@ -193,6 +193,20 @@ installPackages = do
                 let ghcCabalInplace = inplaceBinPath -/- "ghc-cabal" -- HACK?
                 need [ ghcCabalInplace ]
 
+                let cabalFile = pkgCabalFile pkg
+                -- HsColour sources
+                -- QUESTION: what is the output of GhcCabalHsColour?
+                whenM (isSpecified HsColour) $ do
+                    top <- interpretInContext context getTopDirectory
+                    let installDistDir = top -/- buildPath context
+                    -- HACK: copy stuff back to the place favored by ghc-cabal
+                    quietly $ copyDirectoryContents (Not excluded)
+                                  installDistDir (installDistDir -/- "build")
+
+                pkgConf <- pkgConfFile context
+                need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf
+                build $ Target context GhcCabalHsColour [cabalFile] []
+
                 -- HACK (#318): copy stuff back to the place favored by ghc-cabal
                 quietly $ copyDirectoryContents (Not excluded)
                             installDistDir (installDistDir -/- "build")
diff --git a/src/Rules/Wrappers.hs b/src/Rules/Wrappers.hs
index b6f1266..6adf3f7 100644
--- a/src/Rules/Wrappers.hs
+++ b/src/Rules/Wrappers.hs
@@ -109,12 +109,21 @@ hsc2hsWrapper WrappedBinary{..} = do
         , "HSC2HS_EXTRA=\"" ++ hsc2hsExtra ++ "\""
         , contents ]
 
+haddockWrapper :: WrappedBinary -> Expr String
+haddockWrapper WrappedBinary{..} = do
+  lift $ need [sourcePath -/- "Rules/Wrappers.hs"]
+  return $ unlines
+    [ "#!/bin/bash"
+    , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName)
+      ++ " -B" ++ binaryLibPath ++ " -l" ++ binaryLibPath ++ " ${1+\"$@\"}" ]
+
 wrappersCommon :: [(Context, Wrapper)]
 wrappersCommon = [ (vanillaContext Stage0 ghc   , ghcWrapper)
                  , (vanillaContext Stage1 ghc   , ghcWrapper)
                  , (vanillaContext Stage1 hp2ps , hp2psWrapper)
                  , (vanillaContext Stage1 hpc   , hpcWrapper)
-                 , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) ]
+                 , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper)
+                 , (vanillaContext Stage2 haddock, haddockWrapper)]
 
 -- | List of wrappers for inplace artefacts
 inplaceWrappers :: [(Context, Wrapper)]
@@ -127,4 +136,3 @@ installWrappers :: [(Context, Wrapper)]
 installWrappers = wrappersCommon ++
                   [ (vanillaContext Stage0 ghcPkg, installGhcPkgWrapper)
                   , (vanillaContext Stage1 runGhc, installRunGhcWrapper) ]
-



More information about the ghc-commits mailing list