[commit: ghc] wip/nfs-locking: Use GHC to compile C files (#380) (e6dcd1b)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:53:18 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8/ghc
>---------------------------------------------------------------
commit e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8
Author: Zhen Zhang <izgzhen at gmail.com>
Date: Sat Jul 29 18:37:58 2017 +0800
Use GHC to compile C files (#380)
>---------------------------------------------------------------
e6dcd1b0fa05fdb30aa3b9f5bdaf767325ef57e8
src/Builder.hs | 4 ++--
src/Rules/Compile.hs | 6 +++---
src/Settings/Builders/Ghc.hs | 24 +++++++++++++++++++++++-
src/Settings/Default.hs | 1 +
src/Settings/Packages/Base.hs | 2 +-
src/Settings/Packages/Rts.hs | 7 ++++---
6 files changed, 34 insertions(+), 10 deletions(-)
diff --git a/src/Builder.hs b/src/Builder.hs
index 7937319..4112900 100644
--- a/src/Builder.hs
+++ b/src/Builder.hs
@@ -15,8 +15,8 @@ import Stage
-- * Extracting source dependencies, e.g. by passing @-M@ command line argument;
-- * Linking object files & static libraries into an executable.
-- We have CcMode for C compiler and GhcMode for GHC.
-data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show)
-data GhcMode = CompileHs | FindHsDependencies | LinkHs
+data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show)
+data GhcMode = CompileCWithGhc | CompileHs | FindHsDependencies | LinkHs
deriving (Eq, Generic, Show)
-- | GhcPkg can initialise a package database and register packages in it.
diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs
index 87fc39a..d3d2ed5 100644
--- a/src/Rules/Compile.hs
+++ b/src/Rules/Compile.hs
@@ -28,9 +28,9 @@ compilePackage rs context at Context {..} = do
buildWithResources rs $ Target context (Ghc CompileHs stage) [src] [obj]
priority 2.0 $ do
- nonHs "c" %> compile (Cc CompileC ) (obj2src "c" isGeneratedCFile )
- nonHs "cmm" %> compile (Ghc CompileHs) (obj2src "cmm" isGeneratedCmmFile)
- nonHs "s" %> compile (Ghc CompileHs) (obj2src "S" $ const False )
+ nonHs "c" %> compile (Ghc CompileCWithGhc) (obj2src "c" isGeneratedCFile )
+ nonHs "cmm" %> compile (Ghc CompileHs) (obj2src "cmm" isGeneratedCmmFile)
+ nonHs "s" %> compile (Ghc CompileHs) (obj2src "S" $ const False )
-- TODO: Add dependencies for #include of .h and .hs-incl files (gcc -MM?).
[ path <//> "*" <.> suf way | suf <- [ osuf, hisuf] ] &%> compileHs
diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs
index bb7c1e0..b7d5d70 100644
--- a/src/Settings/Builders/Ghc.hs
+++ b/src/Settings/Builders/Ghc.hs
@@ -1,4 +1,7 @@
-module Settings.Builders.Ghc (ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs) where
+module Settings.Builders.Ghc (
+ ghcBuilderArgs, ghcMBuilderArgs, haddockGhcArgs,
+ ghcCbuilderArgs
+) where
import Flavour
import GHC
@@ -15,6 +18,25 @@ ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do
, append =<< getInputs
, arg "-o", arg =<< getOutput ]
+ghcCbuilderArgs :: Args
+ghcCbuilderArgs =
+ builder (Ghc CompileCWithGhc) ? do
+ way <- getWay
+ let ccArgs = [ append =<< getPkgDataList CcArgs
+ , getSettingList . ConfCcArgs =<< getStage
+ , cIncludeArgs
+ , arg "-Werror"
+ , Dynamic `wayUnit` way ? append [ "-fPIC", "-DDYNAMIC" ] ]
+
+ mconcat [ arg "-Wall"
+ , ghcLinkArgs
+ , commonGhcArgs
+ , mconcat (map (map ("-optc" ++) <$>) ccArgs)
+ , arg "-c"
+ , append =<< getInputs
+ , arg "-o"
+ , arg =<< getOutput ]
+
ghcLinkArgs :: Args
ghcLinkArgs = builder (Ghc LinkHs) ? do
stage <- getStage
diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs
index b65e86a..2940406 100644
--- a/src/Settings/Default.hs
+++ b/src/Settings/Default.hs
@@ -212,6 +212,7 @@ defaultBuilderArgs = mconcat
, deriveConstantsBuilderArgs
, genPrimopCodeBuilderArgs
, ghcBuilderArgs
+ , ghcCbuilderArgs
, ghcCabalBuilderArgs
, ghcCabalHsColourBuilderArgs
, ghcMBuilderArgs
diff --git a/src/Settings/Packages/Base.hs b/src/Settings/Packages/Base.hs
index 219c9d4..07c19ce 100644
--- a/src/Settings/Packages/Base.hs
+++ b/src/Settings/Packages/Base.hs
@@ -7,4 +7,4 @@ import Settings
basePackageArgs :: Args
basePackageArgs = package base ? mconcat
[ builder GhcCabal ? arg ("--flags=" ++ integerLibraryName)
- , builder Cc ? arg "-O2" ] -- Fix the 'unknown symbol stat' issue, see #259.
+ , builder (Ghc CompileCWithGhc) ? arg "-optc-O2" ] -- Fix the 'unknown symbol stat' issue, see #259.
diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs
index 5a76eae..87e1fe8 100644
--- a/src/Settings/Packages/Rts.hs
+++ b/src/Settings/Packages/Rts.hs
@@ -48,8 +48,7 @@ rtsPackageArgs = package rts ? do
ffiIncludeDir <- getSetting FfiIncludeDir
ffiLibraryDir <- getSetting FfiLibDir
ghclibDir <- expr installGhcLibDir
- mconcat
- [ builder Cc ? mconcat
+ let cArgs =
[ arg "-Irts"
, arg $ "-I" ++ path
, arg $ "-DRtsWay=\"rts_" ++ show way ++ "\""
@@ -96,8 +95,10 @@ rtsPackageArgs = package rts ? do
append [ "-Wno-incompatible-pointer-types" ]
]
+ mconcat
+ [ builder (Cc FindCDependencies) ? mconcat cArgs
+ , builder (Ghc CompileCWithGhc) ? mconcat (map (map ("-optc" ++) <$>) cArgs)
, builder Ghc ? arg "-Irts"
-
, builder HsCpp ? append
[ "-DTOP=" ++ show top
, "-DFFI_INCLUDE_DIR=" ++ show ffiIncludeDir
More information about the ghc-commits
mailing list