[commit: ghc] wip/nfs-locking: Add binary wrappers for hp2ps, hpc, hsc2hs (#321) (49835af)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 01:19:01 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/49835aff3bd03dd24d00e9c89aaed0339e4aa3a5/ghc
>---------------------------------------------------------------
commit 49835aff3bd03dd24d00e9c89aaed0339e4aa3a5
Author: Zhen Zhang <izgzhen at gmail.com>
Date: Wed Jun 7 18:15:03 2017 +0800
Add binary wrappers for hp2ps, hpc, hsc2hs (#321)
>---------------------------------------------------------------
49835aff3bd03dd24d00e9c89aaed0339e4aa3a5
src/Rules/Program.hs | 12 ++++++++----
src/Rules/Wrappers.hs | 36 ++++++++++++++++++++++++++++++++++--
2 files changed, 42 insertions(+), 6 deletions(-)
diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs
index 79f01f2..5b2e66f 100644
--- a/src/Rules/Program.hs
+++ b/src/Rules/Program.hs
@@ -12,7 +12,8 @@ import Oracles.ModuleFiles
import Oracles.PackageData
import Oracles.Path (topDirectory)
import Rules.Wrappers (WrappedBinary(..), Wrapper,
- ghcWrapper, runGhcWrapper, inplaceGhcPkgWrapper)
+ ghcWrapper, runGhcWrapper, inplaceGhcPkgWrapper,
+ hpcWrapper, hp2psWrapper, hsc2hsWrapper)
import Settings
import Settings.Path (buildPath, inplaceLibBinPath, rtsContext, objectPath,
inplaceLibPath, inplaceBinPath)
@@ -22,10 +23,13 @@ import Util
-- | List of wrappers we build.
wrappers :: [(Context, Wrapper)]
-wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper )
- , (vanillaContext Stage1 ghc , ghcWrapper )
+wrappers = [ (vanillaContext Stage0 ghc , ghcWrapper)
+ , (vanillaContext Stage1 ghc , ghcWrapper)
, (vanillaContext Stage1 runGhc, runGhcWrapper)
- , (vanillaContext Stage0 ghcPkg, inplaceGhcPkgWrapper) ]
+ , (vanillaContext Stage0 ghcPkg, inplaceGhcPkgWrapper)
+ , (vanillaContext Stage1 hp2ps , hp2psWrapper)
+ , (vanillaContext Stage1 hpc , hpcWrapper)
+ , (vanillaContext Stage1 hsc2hs, hsc2hsWrapper) ]
buildProgram :: [(Resource, Int)] -> Context -> Rules ()
buildProgram rs context at Context {..} = when (isProgram package) $ do
diff --git a/src/Rules/Wrappers.hs b/src/Rules/Wrappers.hs
index 93dfee0..246d28a 100644
--- a/src/Rules/Wrappers.hs
+++ b/src/Rules/Wrappers.hs
@@ -1,13 +1,15 @@
module Rules.Wrappers (
WrappedBinary(..), Wrapper, ghcWrapper, runGhcWrapper,
- inplaceGhcPkgWrapper, installGhcPkgWrapper
+ inplaceGhcPkgWrapper, installGhcPkgWrapper, hp2psWrapper,
+ hpcWrapper, hsc2hsWrapper
) where
import Base
-import Expression (Expr, getStage)
+import Expression
import Settings.Install (installPackageDbDirectory)
import Settings.Path (inplacePackageDbDirectory)
import Oracles.Path (getTopDirectory)
+import Oracles.Config.Setting (SettingList(..), settingList)
-- | Wrapper is an expression depending on the 'FilePath' to the
-- | library path and name of the wrapped binary.
@@ -61,3 +63,33 @@ installGhcPkgWrapper WrappedBinary{..} = do
[ "#!/bin/bash"
, "exec " ++ (binaryLibPath -/- "bin" -/- binaryName)
++ " --global-package-db " ++ packageDb ++ " ${1+\"$@\"}" ]
+
+hp2psWrapper :: WrappedBinary -> Expr String
+hp2psWrapper WrappedBinary{..} = do
+ lift $ need [sourcePath -/- "Rules/Wrappers.hs"]
+ return $ unlines
+ [ "#!/bin/bash"
+ , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " ${1+\"$@\"}" ]
+
+hpcWrapper :: WrappedBinary -> Expr String
+hpcWrapper WrappedBinary{..} = do
+ lift $ need [sourcePath -/- "Rules/Wrappers.hs"]
+ return $ unlines
+ [ "#!/bin/bash"
+ , "exec " ++ (binaryLibPath -/- "bin" -/- binaryName) ++ " ${1+\"$@\"}" ]
+
+hsc2hsWrapper :: WrappedBinary -> Expr String
+hsc2hsWrapper WrappedBinary{..} = do
+ top <- getTopDirectory
+ lift $ need [ sourcePath -/- "Rules/Wrappers.hs" ]
+ contents <- lift $ readFile' $ top -/- "utils/hsc2hs/hsc2hs.wrapper"
+ let executableName = binaryLibPath -/- "bin" -/- binaryName
+ confCcArgs <- lift $ settingList (ConfCcArgs Stage1)
+ confGccLinkerArgs <- lift $ settingList (ConfGccLinkerArgs Stage1)
+ let hsc2hsExtra = unwords (map ("-cflags=" ++) confCcArgs) ++ " " ++
+ unwords (map ("-lflags=" ++) confGccLinkerArgs)
+ return $ unlines
+ [ "#!/bin/bash"
+ , "executablename=\"" ++ executableName ++ "\""
+ , "HSC2HS_EXTRA=\"" ++ hsc2hsExtra ++ "\""
+ , contents ]
More information about the ghc-commits
mailing list