Skip to content
Snippets Groups Projects
Commit 7df22eb5 authored by Duncan Coutts's avatar Duncan Coutts
Browse files

Make the -fprof-auto* flags into structured GhcOptions

And add backwards compat support for ghc-7.2 and older that used
the -auto and -auto-all flags.

Simplifies the code in D.S.GHC where we're deciding the options to use.
parent 179e8db8
No related branches found
No related tags found
No related merge requests found
......@@ -471,16 +471,14 @@ buildOrReplLib forRepl verbosity numJobs pkg_descr lbi lib clbi = do
ghcOptHPCDir = hpcdir Hpc.Vanilla
}
profOpts =
let defaultProfOptions = toNubListR [ "-fprof-auto-exported" ]
pkgProfOptions = toNubListR (hcProfOptions GHC libBi)
in vanillaOpts `mappend` mempty {
ghcOptProfilingMode = toFlag True,
ghcOptHiSuffix = toFlag "p_hi",
ghcOptObjSuffix = toFlag "p_o",
ghcOptExtra = defaultProfOptions `mappend` pkgProfOptions,
ghcOptHPCDir = hpcdir Hpc.Prof
}
profOpts = vanillaOpts `mappend` mempty {
ghcOptProfilingMode = toFlag True,
ghcOptProfilingAuto = toFlag GhcProfAutoExported,
ghcOptHiSuffix = toFlag "p_hi",
ghcOptObjSuffix = toFlag "p_o",
ghcOptExtra = toNubListR $ hcProfOptions GHC libBi,
ghcOptHPCDir = hpcdir Hpc.Prof
}
sharedOpts = vanillaOpts `mappend` mempty {
ghcOptDynLinkMode = toFlag GhcDynamicOnly,
......@@ -762,16 +760,14 @@ buildOrReplExe forRepl verbosity numJobs _pkg_descr lbi
ghcOptDynLinkMode = toFlag GhcStaticOnly,
ghcOptHPCDir = hpcdir Hpc.Vanilla
}
profOpts =
let defaultProfOptions = toNubListR [ "-fprof-auto-top" ]
pkgProfOptions = toNubListR (hcProfOptions GHC exeBi)
in baseOpts `mappend` mempty {
ghcOptProfilingMode = toFlag True,
ghcOptHiSuffix = toFlag "p_hi",
ghcOptObjSuffix = toFlag "p_o",
ghcOptExtra = defaultProfOptions `mappend` pkgProfOptions,
ghcOptHPCDir = hpcdir Hpc.Prof
}
profOpts = baseOpts `mappend` mempty {
ghcOptProfilingMode = toFlag True,
ghcOptProfilingAuto = toFlag GhcProfAutoToplevel,
ghcOptHiSuffix = toFlag "p_hi",
ghcOptObjSuffix = toFlag "p_o",
ghcOptExtra = toNubListR (hcProfOptions GHC exeBi),
ghcOptHPCDir = hpcdir Hpc.Prof
}
dynOpts = baseOpts `mappend` mempty {
ghcOptDynLinkMode = toFlag GhcDynamicOnly,
ghcOptHiSuffix = toFlag "dyn_hi",
......@@ -981,15 +977,13 @@ libAbiHash verbosity _pkg_descr lbi lib clbi = do
ghcOptObjSuffix = toFlag "dyn_o",
ghcOptExtra = toNubListR $ hcSharedOptions GHC libBi
}
profArgs =
let defaultProfOptions = toNubListR [ "-fprof-auto-exported" ]
pkgProfOptions = toNubListR (hcProfOptions GHC libBi)
in vanillaArgs `mappend` mempty {
ghcOptProfilingMode = toFlag True,
ghcOptHiSuffix = toFlag "p_hi",
ghcOptObjSuffix = toFlag "p_o",
ghcOptExtra = defaultProfOptions `mappend` pkgProfOptions
}
profArgs = vanillaArgs `mappend` mempty {
ghcOptProfilingMode = toFlag True,
ghcOptProfilingAuto = toFlag GhcProfAutoExported,
ghcOptHiSuffix = toFlag "p_hi",
ghcOptObjSuffix = toFlag "p_o",
ghcOptExtra = toNubListR $ hcProfOptions GHC libBi
}
ghcArgs = if withVanillaLib lbi then vanillaArgs
else if withSharedLib lbi then sharedArgs
else if withProfLib lbi then profArgs
......
......@@ -47,6 +47,7 @@ data GhcImplInfo = GhcImplInfo
, reportsNoExt :: Bool -- ^ --supported-languages gives Ext and NoExt
, alwaysNondecIndent :: Bool -- ^ NondecreasingIndentation is always on
, flagGhciScript :: Bool -- ^ -ghci-script flag supported
, flagProfAuto :: Bool -- ^ new style -fprof-auto* flags
, flagPackageConf :: Bool -- ^ use package-conf instead of package-db
, flagDebugInfo :: Bool -- ^ -g flag supported
}
......@@ -80,6 +81,7 @@ ghcVersionImplInfo (Version v _) = GhcImplInfo
, reportsNoExt = v >= [7]
, alwaysNondecIndent = v < [7,1]
, flagGhciScript = v >= [7,2]
, flagProfAuto = v >= [7,4]
, flagPackageConf = v < [7,5]
, flagDebugInfo = v >= [7,10]
}
......@@ -100,6 +102,7 @@ ghcjsVersionImplInfo _ghcjsVer _ghcVer = GhcImplInfo
, reportsNoExt = True
, alwaysNondecIndent = False
, flagGhciScript = True
, flagProfAuto = True
, flagPackageConf = False
, flagDebugInfo = False
}
......
......@@ -4,6 +4,7 @@ module Distribution.Simple.Program.GHC (
GhcMode(..),
GhcOptimisation(..),
GhcDynLinkMode(..),
GhcProfAuto(..),
ghcInvocation,
renderGhcOptions,
......@@ -161,6 +162,9 @@ data GhcOptions = GhcOptions {
-- | Compile in profiling mode; the @ghc -prof@ flag.
ghcOptProfilingMode :: Flag Bool,
-- | Automatically add profiling cost centers; the @ghc -fprof-auto*@ flags.
ghcOptProfilingAuto :: Flag GhcProfAuto,
-- | Use the \"split object files\" feature; the @ghc -split-objs@ flag.
ghcOptSplitObjs :: Flag Bool,
......@@ -230,6 +234,10 @@ data GhcDynLinkMode = GhcStaticOnly -- ^ @-static@
| GhcStaticAndDynamic -- ^ @-static -dynamic-too@
deriving (Show, Eq)
data GhcProfAuto = GhcProfAutoAll -- ^ @-fprof-auto@
| GhcProfAutoToplevel -- ^ @-fprof-auto-top@
| GhcProfAutoExported -- ^ @-fprof-auto-exported@
deriving (Show, Eq)
runGHC :: Verbosity -> ConfiguredProgram -> Compiler -> GhcOptions -> IO ()
runGHC verbosity ghcProg comp opts = do
......@@ -283,6 +291,18 @@ renderGhcOptions comp opts
, [ "-prof" | flagBool ghcOptProfilingMode ]
, case flagToMaybe (ghcOptProfilingAuto opts) of
Nothing -> []
Just GhcProfAutoAll
| flagProfAuto implInfo -> ["-fprof-auto"]
| otherwise -> ["-auto-all"] -- not the same, but close
Just GhcProfAutoToplevel
| flagProfAuto implInfo -> ["-fprof-auto-top"]
| otherwise -> ["-auto-all"]
Just GhcProfAutoExported
| flagProfAuto implInfo -> ["-fprof-auto-exported"]
| otherwise -> ["-auto"]
, [ "-split-objs" | flagBool ghcOptSplitObjs ]
, case flagToMaybe (ghcOptHPCDir opts) of
......@@ -485,6 +505,7 @@ instance Monoid GhcOptions where
ghcOptOptimisation = mempty,
ghcOptDebugInfo = mempty,
ghcOptProfilingMode = mempty,
ghcOptProfilingAuto = mempty,
ghcOptSplitObjs = mempty,
ghcOptNumJobs = mempty,
ghcOptHPCDir = mempty,
......@@ -538,6 +559,7 @@ instance Monoid GhcOptions where
ghcOptOptimisation = combine ghcOptOptimisation,
ghcOptDebugInfo = combine ghcOptDebugInfo,
ghcOptProfilingMode = combine ghcOptProfilingMode,
ghcOptProfilingAuto = combine ghcOptProfilingAuto,
ghcOptSplitObjs = combine ghcOptSplitObjs,
ghcOptNumJobs = combine ghcOptNumJobs,
ghcOptHPCDir = combine ghcOptHPCDir,
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment