summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorEthan Kiang <chocopuff298@gmail.com>2021-06-22 21:34:34 +0800
committersheaf <sam.derbyshire@gmail.com>2022-05-19 13:06:27 +0200
commit8183c5f5ebddac81cc3fdf95bd0da51fb110565d (patch)
treebec49828828ec4e4f392e0fee0755f9506088e1e
parent8bb0547b5a013bbafbfcd082930cb29182832baf (diff)
downloadhaskell-8183c5f5ebddac81cc3fdf95bd0da51fb110565d.tar.gz
Pass '-x c++' and '-std=c++11' to `cc` for cpp files, in Hadrian
'-x c++' was found to be required on Darwin Clang 11 and 12. '-std=c++' was found to be needed on Clang 12 but not 11.
-rw-r--r--hadrian/src/Builder.hs13
-rw-r--r--hadrian/src/Rules/Compile.hs12
-rwxr-xr-xhadrian/src/Settings.hs2
-rw-r--r--hadrian/src/Settings/Builders/Cc.hs12
-rw-r--r--hadrian/src/Settings/Packages.hs3
5 files changed, 29 insertions, 13 deletions
diff --git a/hadrian/src/Builder.hs b/hadrian/src/Builder.hs
index 1e471b2a26..d9b7072071 100644
--- a/hadrian/src/Builder.hs
+++ b/hadrian/src/Builder.hs
@@ -1,9 +1,9 @@
{-# LANGUAGE InstanceSigs, TypeOperators #-}
module Builder (
-- * Data types
- ArMode (..), CcMode (..), ConfigurationInfo (..), GhcMode (..),
- GhcPkgMode (..), HaddockMode (..), SphinxMode (..), TarMode (..),
- Builder (..),
+ ArMode (..), CcMode (..), ConfigurationInfo (..), DependencyType (..),
+ GhcMode (..), GhcPkgMode (..), HaddockMode (..), SphinxMode (..),
+ TarMode (..), Builder (..),
-- * Builder properties
builderProvenance, systemBuilderPath, builderPath, isSpecified, needBuilder,
@@ -41,12 +41,17 @@ import Packages
-- | C compiler can be used in two different modes:
-- * Compile or preprocess a source file.
-- * Extract source dependencies by passing @-MM@ command line argument.
-data CcMode = CompileC | FindCDependencies deriving (Eq, Generic, Show)
+data CcMode = CompileC | FindCDependencies DependencyType deriving (Eq, Generic, Show)
+data DependencyType = CDep | CxxDep deriving (Eq, Generic, Show)
instance Binary CcMode
instance Hashable CcMode
instance NFData CcMode
+instance Binary DependencyType
+instance Hashable DependencyType
+instance NFData DependencyType
+
-- | GHC can be used in four different modes:
-- * Compile a Haskell source file.
-- * Compile a C source file.
diff --git a/hadrian/src/Rules/Compile.hs b/hadrian/src/Rules/Compile.hs
index b21bcaf74b..f093d15b96 100644
--- a/hadrian/src/Rules/Compile.hs
+++ b/hadrian/src/Rules/Compile.hs
@@ -239,7 +239,7 @@ compileNonHsObject rs lang path = do
Cmm -> obj2src "cmm" isGeneratedCmmFile ctx path
Cxx -> obj2src "cpp" (const False) ctx path
need [src]
- needDependencies ctx src (path <.> "d")
+ needDependencies lang ctx src (path <.> "d")
buildWithResources rs $ target ctx (builder stage) [src] [path]
-- * Helpers
@@ -247,11 +247,11 @@ compileNonHsObject rs lang path = do
-- | Discover dependencies of a given source file by iteratively calling @gcc@
-- in the @-MM -MG@ mode and building generated dependencies if they are missing
-- until reaching a fixed point.
-needDependencies :: Context -> FilePath -> FilePath -> Action ()
-needDependencies context@Context {..} src depFile = discover
+needDependencies :: SourceLang -> Context -> FilePath -> FilePath -> Action ()
+needDependencies lang context@Context {..} src depFile = discover
where
discover = do
- build $ target context (Cc FindCDependencies stage) [src] [depFile]
+ build $ target context (Cc (FindCDependencies depType) stage) [src] [depFile]
deps <- parseFile depFile
-- Generated dependencies, if not yet built, will not be found and hence
-- will be referred to simply by their file names.
@@ -266,6 +266,10 @@ needDependencies context@Context {..} src depFile = discover
need todo -- Build newly discovered generated dependencies
discover -- Continue the discovery process
+ -- We need to pass different flags to cc depending on whether the
+ -- file to compile is a .c or a .cpp file
+ depType = if lang == Cxx then CxxDep else CDep
+
parseFile :: FilePath -> Action [String]
parseFile file = do
input <- liftIO $ readFile file
diff --git a/hadrian/src/Settings.hs b/hadrian/src/Settings.hs
index ec61c62026..79c42414b3 100755
--- a/hadrian/src/Settings.hs
+++ b/hadrian/src/Settings.hs
@@ -304,7 +304,7 @@ builderSetting =
ccBuilder =
[ ("c", CompileC)
- , ("deps", FindCDependencies)
+ , ("deps", FindCDependencies CDep)
]
stages = map (\stg -> (stageString stg, stg)) [minBound..maxBound]
diff --git a/hadrian/src/Settings/Builders/Cc.hs b/hadrian/src/Settings/Builders/Cc.hs
index e0055f3e8b..f7bf215f26 100644
--- a/hadrian/src/Settings/Builders/Cc.hs
+++ b/hadrian/src/Settings/Builders/Cc.hs
@@ -17,12 +17,18 @@ ccBuilderArgs = do
, arg "-c", arg =<< getInput
, arg "-o", arg =<< getOutput ]
- , builder (Cc FindCDependencies) ? do
+ , builder (Cc (FindCDependencies CDep)) ? findCDepExpr CDep
+ , builder (Cc (FindCDependencies CxxDep)) ? findCDepExpr CxxDep
+ ]
+ where
+ findCDepExpr depType = do
output <- getOutput
mconcat [ arg "-E"
, arg "-MM", arg "-MG"
, arg "-MF", arg output
, arg "-MT", arg $ dropExtension output -<.> "o"
+ , case depType of CDep -> mempty; CxxDep -> arg "-std=c++11"
, cIncludeArgs
- , arg "-x", arg "c"
- , arg =<< getInput ] ]
+ , arg "-x", arg (case depType of CDep -> "c"; CxxDep -> "c++")
+ , arg =<< getInput
+ ]
diff --git a/hadrian/src/Settings/Packages.hs b/hadrian/src/Settings/Packages.hs
index deba4860d5..7848eb63a4 100644
--- a/hadrian/src/Settings/Packages.hs
+++ b/hadrian/src/Settings/Packages.hs
@@ -374,7 +374,8 @@ rtsPackageArgs = package rts ? do
, cabalExtraDirs libnumaIncludeDir libnumaLibraryDir
, useSystemFfi ? cabalExtraDirs ffiIncludeDir ffiLibraryDir
]
- , builder (Cc FindCDependencies) ? cArgs
+ , builder (Cc (FindCDependencies CDep)) ? cArgs
+ , builder (Cc (FindCDependencies CxxDep)) ? cArgs
, builder (Ghc CompileCWithGhc) ? map ("-optc" ++) <$> cArgs
, builder (Ghc CompileCppWithGhc) ? map ("-optcxx" ++) <$> cArgs
, builder Ghc ? ghcArgs