[commit: ghc] wip/nfs-locking: Build touchy, fix #125. (fee02d9)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:30:12 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3/ghc
>---------------------------------------------------------------
commit fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Thu Jan 7 12:59:47 2016 +0000
Build touchy, fix #125.
>---------------------------------------------------------------
fee02d9c15ad5e2efa1387690e8ed7115c6c9dd3
src/GHC.hs | 14 +++++++++-----
src/Rules/Data.hs | 8 ++++++++
src/Settings/Args.hs | 4 +++-
src/Settings/Packages.hs | 3 ++-
src/Settings/Packages/{Hp2ps.hs => Touchy.hs} | 8 ++++----
5 files changed, 26 insertions(+), 11 deletions(-)
diff --git a/src/GHC.hs b/src/GHC.hs
index d4d5511..6e3a477 100644
--- a/src/GHC.hs
+++ b/src/GHC.hs
@@ -6,7 +6,7 @@ module GHC (
haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp,
integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty,
primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time,
- transformers, unix, win32, xhtml,
+ touchy, transformers, unix, win32, xhtml,
defaultKnownPackages, defaultTargetDirectory, defaultProgramPath
) where
@@ -28,7 +28,7 @@ defaultKnownPackages =
, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp
, integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty
, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time
- , transformers, unix, win32, xhtml ]
+ , touchy, transformers, unix, win32, xhtml ]
-- Package definitions (see Package.hs)
array, base, binary, bytestring, cabal, compiler, containers, compareSizes,
@@ -37,7 +37,7 @@ array, base, binary, bytestring, cabal, compiler, containers, compareSizes,
haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp,
integerSimple, iservBin, libffi, mkUserGuidePart, parallel, pretty,
primitive, process, rts, runGhc, stm, templateHaskell, terminfo, time,
- transformers, unix, win32, xhtml :: Package
+ touchy, transformers, unix, win32, xhtml :: Package
array = library "array"
base = library "base"
@@ -83,6 +83,7 @@ stm = library "stm"
templateHaskell = library "template-haskell"
terminfo = library "terminfo"
time = library "time"
+touchy = utility "touchy"
transformers = library "transformers"
unix = library "unix"
win32 = library "Win32"
@@ -92,7 +93,7 @@ xhtml = library "xhtml"
-- TODO: The following utils are not included into the build system because
-- they seem to be unused or unrelated to the build process: checkUniques,
-- completion, count_lines, coverity, debugNGC, describe-unexpected, genargs,
--- lndir, mkdirhier, testremove, touchy, vagrant
+-- lndir, mkdirhier, testremove, vagrant
-- GHC build results will be placed into target directories with the following
-- typical structure:
@@ -102,7 +103,7 @@ xhtml = library "xhtml"
defaultTargetDirectory :: Stage -> Package -> FilePath
defaultTargetDirectory stage _ = stageString stage
--- TODO: simplify
+-- TODO: simplify, add programInplaceLibPath
-- | Returns a relative path to the program executable
defaultProgramPath :: Stage -> Package -> Maybe FilePath
defaultProgramPath stage pkg
@@ -110,6 +111,9 @@ defaultProgramPath stage pkg
| pkg == haddock || pkg == ghcTags = case stage of
Stage2 -> Just . inplaceProgram $ pkgNameString pkg
_ -> Nothing
+ | pkg == touchy = case stage of
+ Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe
+ _ -> Nothing
| isProgram pkg = case stage of
Stage0 -> Just . inplaceProgram $ pkgNameString pkg
_ -> Just . installProgram $ pkgNameString pkg
diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs
index ee15c19..46072ce 100644
--- a/src/Rules/Data.hs
+++ b/src/Rules/Data.hs
@@ -67,6 +67,14 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do
writeFileChanged mk contents
putSuccess $ "| Successfully generated '" ++ mk ++ "'."
+ when (pkg == touchy) $ dataFile %> \mk -> do
+ let prefix = "utils_touchy_" ++ stageString stage ++ "_"
+ contents = unlines $ map (prefix++)
+ [ "PROGNAME = touchy"
+ , "C_SRCS = touchy.c" ]
+ writeFileChanged mk contents
+ putSuccess $ "| Successfully generated '" ++ mk ++ "'."
+
-- Bootstrapping `ghcCabal`: although `ghcCabal` is a proper cabal
-- package, we cannot generate the corresponding `package-data.mk` file
-- by running by running `ghcCabal`, because it has not yet been built.
diff --git a/src/Settings/Args.hs b/src/Settings/Args.hs
index fb121ed..f2b30fa 100644
--- a/src/Settings/Args.hs
+++ b/src/Settings/Args.hs
@@ -30,6 +30,7 @@ import Settings.Packages.IntegerGmp
import Settings.Packages.IservBin
import Settings.Packages.Rts
import Settings.Packages.RunGhc
+import Settings.Packages.Touchy
import Settings.User
getArgs :: Expr [String]
@@ -75,4 +76,5 @@ defaultPackageArgs = mconcat
, integerGmpPackageArgs
, iservBinPackageArgs
, rtsPackageArgs
- , runGhcPackageArgs ]
+ , runGhcPackageArgs
+ , touchyPackageArgs ]
diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs
index dba4054..f80f0d0 100644
--- a/src/Settings/Packages.hs
+++ b/src/Settings/Packages.hs
@@ -24,7 +24,8 @@ packagesStage0 = mconcat
[ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg
, hsc2hs, hoopl, hpc, templateHaskell, transformers ]
-- the stage0 predicate makes sure these packages are built only in Stage0
- , stage0 ? append [deriveConstants, dllSplit, genapply, genprimopcode, hp2ps]
+ , stage0 ? append [ deriveConstants, dllSplit, genapply, genprimopcode
+ , hp2ps, touchy ]
, notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ]
packagesStage1 :: Packages
diff --git a/src/Settings/Packages/Hp2ps.hs b/src/Settings/Packages/Touchy.hs
similarity index 72%
copy from src/Settings/Packages/Hp2ps.hs
copy to src/Settings/Packages/Touchy.hs
index 26518c6..8345449 100644
--- a/src/Settings/Packages/Hp2ps.hs
+++ b/src/Settings/Packages/Touchy.hs
@@ -1,13 +1,13 @@
-module Settings.Packages.Hp2ps (hp2psPackageArgs) where
+module Settings.Packages.Touchy (touchyPackageArgs) where
import Base
import Expression
-import GHC (hp2ps)
+import GHC (touchy)
import Predicates (builderGhc, package)
import Settings
-hp2psPackageArgs :: Args
-hp2psPackageArgs = package hp2ps ? do
+touchyPackageArgs :: Args
+touchyPackageArgs = package touchy ? do
path <- getTargetPath
let cabalMacros = path -/- "build/autogen/cabal_macros.h"
mconcat [ builderGhc ?
More information about the ghc-commits
mailing list