{-# LANGUAGE RecordWildCards #-}

-- | This module manages storing the various GHC option flags in a modules
-- interface file as part of the recompilation checking infrastructure.
module GHC.Iface.Recomp.Flags (
        fingerprintDynFlags
      , fingerprintOptFlags
      , fingerprintHpcFlags
    ) where

import GHC.Prelude

import GHC.Utils.Binary
import GHC.Driver.Session
import GHC.Driver.Types
import GHC.Unit.Module
import GHC.Types.Name
import GHC.Utils.Fingerprint
import GHC.Iface.Recomp.Binary
-- import GHC.Utils.Outputable

import GHC.Data.EnumSet as EnumSet
import System.FilePath (normalise)

-- | Produce a fingerprint of a @DynFlags@ value. We only base
-- the finger print on important fields in @DynFlags@ so that
-- the recompilation checker can use this fingerprint.
--
-- NB: The 'Module' parameter is the 'Module' recorded by the
-- *interface* file, not the actual 'Module' according to our
-- 'DynFlags'.
fingerprintDynFlags :: DynFlags -> Module
                    -> (BinHandle -> Name -> IO ())
                    -> IO Fingerprint

fingerprintDynFlags :: DynFlags
-> Module -> (BinHandle -> Name -> IO ()) -> IO Fingerprint
fingerprintDynFlags dflags :: DynFlags
dflags@DynFlags{Bool
Int
FilePath
[Int]
[FilePath]
[(FilePath, FilePath)]
[(ModuleName, FilePath)]
[(ModuleName, Module)]
[ModuleName]
[IgnorePackageFlag]
[PackageDBFlag]
[PackageFlag]
[TrustFlag]
[Option]
[OnOff Extension]
[LoadedPlugin]
[StaticPlugin]
Maybe Int
Maybe FilePath
Maybe [UnitDatabase UnitId]
Maybe (FilePath, Int)
Maybe IndefUnitId
Maybe Language
Maybe SseVersion
Maybe BmiVersion
Word
IORef Bool
IORef Int
IORef (Maybe CompilerInfo)
IORef (Maybe LinkerInfo)
IORef (Map FilePath FilePath)
IORef (Set FilePath)
IORef (ModuleEnv Int)
IORef FilesToClean
Set Way
SrcSpan
UnitState
Module
UnitId
Platform
IntWithInf
OverridingBool
Scheme
SafeHaskellMode
HscTarget
CfgWeights
DynLibLoader
FlushErr
FlushOut
GhcLink
GhcMode
IncludeSpecs
LlvmConfig
ProfAuto
RtsOptsEnabled
PlatformMisc
FileSettings
GhcNameVersion
PlatformConstants
ToolSettings
Hooks
EnumSet Extension
EnumSet DumpFlag
EnumSet GeneralFlag
EnumSet WarningFlag
DumpAction
LogAction
TraceAction
ways :: DynFlags -> Set Way
warningFlags :: DynFlags -> EnumSet WarningFlag
warnUnsafeOnLoc :: DynFlags -> SrcSpan
warnSafeOnLoc :: DynFlags -> SrcSpan
verbosity :: DynFlags -> Int
useUnicode :: DynFlags -> Bool
useColor :: DynFlags -> OverridingBool
unitState :: DynFlags -> UnitState
unitDatabases :: DynFlags -> Maybe [UnitDatabase UnitId]
uniqueIncrement :: DynFlags -> Int
ufVeryAggressive :: DynFlags -> Bool
ufUseThreshold :: DynFlags -> Int
ufFunAppDiscount :: DynFlags -> Int
ufDictDiscount :: DynFlags -> Int
ufDearOp :: DynFlags -> Int
ufCreationThreshold :: DynFlags -> Int
trustworthyOnLoc :: DynFlags -> SrcSpan
trustFlags :: DynFlags -> [TrustFlag]
trace_action :: DynFlags -> TraceAction
toolSettings :: DynFlags -> ToolSettings
thOnLoc :: DynFlags -> SrcSpan
targetPlatform :: DynFlags -> Platform
stubDir :: DynFlags -> Maybe FilePath
strictnessBefore :: DynFlags -> [Int]
staticPlugins :: DynFlags -> [StaticPlugin]
sseVersion :: DynFlags -> Maybe SseVersion
splitInfo :: DynFlags -> Maybe (FilePath, Int)
specConstrThreshold :: DynFlags -> Maybe Int
specConstrRecursive :: DynFlags -> Int
specConstrCount :: DynFlags -> Maybe Int
solverIterations :: DynFlags -> IntWithInf
simplTickFactor :: DynFlags -> Int
simplPhases :: DynFlags -> Int
safeInferred :: DynFlags -> Bool
safeInfer :: DynFlags -> Bool
safeHaskell :: DynFlags -> SafeHaskellMode
ruleCheck :: DynFlags -> Maybe FilePath
rtsOptsSuggestions :: DynFlags -> Bool
rtsOptsEnabled :: DynFlags -> RtsOptsEnabled
rtsOpts :: DynFlags -> Maybe FilePath
rtldInfo :: DynFlags -> IORef (Maybe LinkerInfo)
rtccInfo :: DynFlags -> IORef (Maybe CompilerInfo)
reverseErrors :: DynFlags -> Bool
refLevelHoleFits :: DynFlags -> Maybe Int
reductionDepth :: DynFlags -> IntWithInf
rawSettings :: DynFlags -> [(FilePath, FilePath)]
profAuto :: DynFlags -> ProfAuto
pprUserLength :: DynFlags -> Int
pprCols :: DynFlags -> Int
pluginPackageFlags :: DynFlags -> [PackageFlag]
pluginModNames :: DynFlags -> [ModuleName]
pluginModNameOpts :: DynFlags -> [(ModuleName, FilePath)]
platformMisc :: DynFlags -> PlatformMisc
platformConstants :: DynFlags -> PlatformConstants
pkgTrustOnLoc :: DynFlags -> SrcSpan
parMakeCount :: DynFlags -> Maybe Int
packageFlags :: DynFlags -> [PackageFlag]
packageEnv :: DynFlags -> Maybe FilePath
packageDBFlags :: DynFlags -> [PackageDBFlag]
overlapInstLoc :: DynFlags -> SrcSpan
outputHi :: DynFlags -> Maybe FilePath
outputFile :: DynFlags -> Maybe FilePath
optLevel :: DynFlags -> Int
objectSuf :: DynFlags -> FilePath
objectDir :: DynFlags -> Maybe FilePath
nextWrapperNum :: DynFlags -> IORef (ModuleEnv Int)
nextTempSuffix :: DynFlags -> IORef Int
newDerivOnLoc :: DynFlags -> SrcSpan
maxWorkerArgs :: DynFlags -> Int
maxValidHoleFits :: DynFlags -> Maybe Int
maxUncoveredPatterns :: DynFlags -> Int
maxSimplIterations :: DynFlags -> Int
maxRelevantBinds :: DynFlags -> Maybe Int
maxRefHoleFits :: DynFlags -> Maybe Int
maxPmCheckModels :: DynFlags -> Int
maxInlineMemsetInsns :: DynFlags -> Int
maxInlineMemcpyInsns :: DynFlags -> Int
maxInlineAllocSize :: DynFlags -> Int
maxErrors :: DynFlags -> Maybe Int
mainModIs :: DynFlags -> Module
mainFunIs :: DynFlags -> Maybe FilePath
log_action :: DynFlags -> LogAction
llvmConfig :: DynFlags -> LlvmConfig
liftLamsRecArgs :: DynFlags -> Maybe Int
liftLamsNonRecArgs :: DynFlags -> Maybe Int
liftLamsKnown :: DynFlags -> Bool
libraryPaths :: DynFlags -> [FilePath]
liberateCaseThreshold :: DynFlags -> Maybe Int
ldInputs :: DynFlags -> [Option]
language :: DynFlags -> Maybe Language
interactivePrint :: DynFlags -> Maybe FilePath
inlineCheck :: DynFlags -> Maybe FilePath
initialUnique :: DynFlags -> Int
incoherentOnLoc :: DynFlags -> SrcSpan
includePaths :: DynFlags -> IncludeSpecs
importPaths :: DynFlags -> [FilePath]
ignorePackageFlags :: DynFlags -> [IgnorePackageFlag]
hscTarget :: DynFlags -> HscTarget
hpcDir :: DynFlags -> FilePath
hooks :: DynFlags -> Hooks
homeUnitInstantiations :: DynFlags -> [(ModuleName, Module)]
homeUnitInstanceOfId :: DynFlags -> Maybe IndefUnitId
homeUnitId :: DynFlags -> UnitId
historySize :: DynFlags -> Int
hieSuf :: DynFlags -> FilePath
hieDir :: DynFlags -> Maybe FilePath
hiSuf :: DynFlags -> FilePath
hiDir :: DynFlags -> Maybe FilePath
hcSuf :: DynFlags -> FilePath
haddockOptions :: DynFlags -> Maybe FilePath
ghciScripts :: DynFlags -> [FilePath]
ghciHistSize :: DynFlags -> Int
ghcVersionFile :: DynFlags -> Maybe FilePath
ghcNameVersion :: DynFlags -> GhcNameVersion
ghcMode :: DynFlags -> GhcMode
ghcLink :: DynFlags -> GhcLink
ghcHeapSize :: DynFlags -> Maybe Int
generatedDumps :: DynFlags -> IORef (Set FilePath)
generalFlags :: DynFlags -> EnumSet GeneralFlag
frontendPluginOpts :: DynFlags -> [FilePath]
frameworkPaths :: DynFlags -> [FilePath]
flushOut :: DynFlags -> FlushOut
flushErr :: DynFlags -> FlushErr
floatLamArgs :: DynFlags -> Maybe Int
filesToClean :: DynFlags -> IORef FilesToClean
fileSettings :: DynFlags -> FileSettings
fatalWarningFlags :: DynFlags -> EnumSet WarningFlag
extensions :: DynFlags -> [OnOff Extension]
extensionFlags :: DynFlags -> EnumSet Extension
enableTimeStats :: DynFlags -> Bool
dynOutputFile :: DynFlags -> Maybe FilePath
dynObjectSuf :: DynFlags -> FilePath
dynLibLoader :: DynFlags -> DynLibLoader
dynHiSuf :: DynFlags -> FilePath
dylibInstallName :: DynFlags -> Maybe FilePath
dump_action :: DynFlags -> DumpAction
dumpPrefixForce :: DynFlags -> Maybe FilePath
dumpPrefix :: DynFlags -> Maybe FilePath
dumpFlags :: DynFlags -> EnumSet DumpFlag
dumpDir :: DynFlags -> Maybe FilePath
dirsToClean :: DynFlags -> IORef (Map FilePath FilePath)
depSuffixes :: DynFlags -> [FilePath]
depMakefile :: DynFlags -> FilePath
depIncludePkgDeps :: DynFlags -> Bool
depIncludeCppDeps :: DynFlags -> Bool
depExcludeMods :: DynFlags -> [ModuleName]
debugLevel :: DynFlags -> Int
colScheme :: DynFlags -> Scheme
cmmProcAlignment :: DynFlags -> Maybe Int
cmdlineFrameworks :: DynFlags -> [FilePath]
cfgWeightInfo :: DynFlags -> CfgWeights
canUseColor :: DynFlags -> Bool
canGenerateDynamicToo :: DynFlags -> IORef Bool
cachedPlugins :: DynFlags -> [LoadedPlugin]
bmiVersion :: DynFlags -> Maybe BmiVersion
binBlobThreshold :: DynFlags -> Word
avx512pf :: DynFlags -> Bool
avx512f :: DynFlags -> Bool
avx512er :: DynFlags -> Bool
avx512cd :: DynFlags -> Bool
avx2 :: DynFlags -> Bool
avx :: DynFlags -> Bool
cfgWeightInfo :: CfgWeights
uniqueIncrement :: Int
initialUnique :: Int
maxErrors :: Maybe Int
reverseErrors :: Bool
maxInlineMemsetInsns :: Int
maxInlineMemcpyInsns :: Int
maxInlineAllocSize :: Int
rtccInfo :: IORef (Maybe CompilerInfo)
rtldInfo :: IORef (Maybe LinkerInfo)
avx512pf :: Bool
avx512f :: Bool
avx512er :: Bool
avx512cd :: Bool
avx2 :: Bool
avx :: Bool
bmiVersion :: Maybe BmiVersion
sseVersion :: Maybe SseVersion
nextWrapperNum :: IORef (ModuleEnv Int)
interactivePrint :: Maybe FilePath
profAuto :: ProfAuto
colScheme :: Scheme
canUseColor :: Bool
useColor :: OverridingBool
useUnicode :: Bool
pprCols :: Int
pprUserLength :: Int
ghciScripts :: [FilePath]
haddockOptions :: Maybe FilePath
ghcVersionFile :: Maybe FilePath
flushErr :: FlushErr
flushOut :: FlushOut
trace_action :: TraceAction
dump_action :: DumpAction
log_action :: LogAction
ghciHistSize :: Int
maxWorkerArgs :: Int
ufVeryAggressive :: Bool
ufDearOp :: Int
ufDictDiscount :: Int
ufFunAppDiscount :: Int
ufUseThreshold :: Int
ufCreationThreshold :: Int
extensionFlags :: EnumSet Extension
extensions :: [OnOff Extension]
trustworthyOnLoc :: SrcSpan
warnUnsafeOnLoc :: SrcSpan
warnSafeOnLoc :: SrcSpan
pkgTrustOnLoc :: SrcSpan
incoherentOnLoc :: SrcSpan
overlapInstLoc :: SrcSpan
newDerivOnLoc :: SrcSpan
thOnLoc :: SrcSpan
safeInferred :: Bool
safeInfer :: Bool
safeHaskell :: SafeHaskellMode
language :: Maybe Language
fatalWarningFlags :: EnumSet WarningFlag
warningFlags :: EnumSet WarningFlag
generalFlags :: EnumSet GeneralFlag
dumpFlags :: EnumSet DumpFlag
generatedDumps :: IORef (Set FilePath)
nextTempSuffix :: IORef Int
dirsToClean :: IORef (Map FilePath FilePath)
filesToClean :: IORef FilesToClean
unitState :: UnitState
unitDatabases :: Maybe [UnitDatabase UnitId]
packageEnv :: Maybe FilePath
trustFlags :: [TrustFlag]
pluginPackageFlags :: [PackageFlag]
packageFlags :: [PackageFlag]
ignorePackageFlags :: [IgnorePackageFlag]
packageDBFlags :: [PackageDBFlag]
depSuffixes :: [FilePath]
depExcludeMods :: [ModuleName]
depIncludeCppDeps :: Bool
depIncludePkgDeps :: Bool
depMakefile :: FilePath
hooks :: Hooks
staticPlugins :: [StaticPlugin]
cachedPlugins :: [LoadedPlugin]
frontendPluginOpts :: [FilePath]
pluginModNameOpts :: [(ModuleName, FilePath)]
pluginModNames :: [ModuleName]
hpcDir :: FilePath
rtsOptsSuggestions :: Bool
rtsOptsEnabled :: RtsOptsEnabled
rtsOpts :: Maybe FilePath
cmdlineFrameworks :: [FilePath]
frameworkPaths :: [FilePath]
libraryPaths :: [FilePath]
includePaths :: IncludeSpecs
ldInputs :: [Option]
dumpPrefixForce :: Maybe FilePath
dumpPrefix :: Maybe FilePath
dynLibLoader :: DynLibLoader
outputHi :: Maybe FilePath
dynOutputFile :: Maybe FilePath
outputFile :: Maybe FilePath
dynHiSuf :: FilePath
dynObjectSuf :: FilePath
canGenerateDynamicToo :: IORef Bool
hieSuf :: FilePath
hiSuf :: FilePath
hcSuf :: FilePath
objectSuf :: FilePath
dumpDir :: Maybe FilePath
stubDir :: Maybe FilePath
hieDir :: Maybe FilePath
hiDir :: Maybe FilePath
dylibInstallName :: Maybe FilePath
objectDir :: Maybe FilePath
splitInfo :: Maybe (FilePath, Int)
ways :: Set Way
homeUnitInstantiations :: [(ModuleName, Module)]
homeUnitInstanceOfId :: Maybe IndefUnitId
homeUnitId :: UnitId
solverIterations :: IntWithInf
reductionDepth :: IntWithInf
mainFunIs :: Maybe FilePath
mainModIs :: Module
importPaths :: [FilePath]
historySize :: Int
cmmProcAlignment :: Maybe Int
liftLamsKnown :: Bool
liftLamsNonRecArgs :: Maybe Int
liftLamsRecArgs :: Maybe Int
floatLamArgs :: Maybe Int
liberateCaseThreshold :: Maybe Int
binBlobThreshold :: Word
specConstrRecursive :: Int
specConstrCount :: Maybe Int
specConstrThreshold :: Maybe Int
simplTickFactor :: Int
maxPmCheckModels :: Int
maxUncoveredPatterns :: Int
refLevelHoleFits :: Maybe Int
maxRefHoleFits :: Maybe Int
maxValidHoleFits :: Maybe Int
maxRelevantBinds :: Maybe Int
ghcHeapSize :: Maybe Int
enableTimeStats :: Bool
parMakeCount :: Maybe Int
strictnessBefore :: [Int]
inlineCheck :: Maybe FilePath
ruleCheck :: Maybe FilePath
maxSimplIterations :: Int
simplPhases :: Int
debugLevel :: Int
optLevel :: Int
verbosity :: Int
llvmConfig :: LlvmConfig
rawSettings :: [(FilePath, FilePath)]
platformConstants :: PlatformConstants
platformMisc :: PlatformMisc
toolSettings :: ToolSettings
targetPlatform :: Platform
fileSettings :: FileSettings
ghcNameVersion :: GhcNameVersion
hscTarget :: HscTarget
ghcLink :: GhcLink
ghcMode :: GhcMode
..} Module
this_mod BinHandle -> Name -> IO ()
nameio =
    let mainis :: Maybe (Maybe FilePath)
mainis   = if Module
mainModIs Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
this_mod then Maybe FilePath -> Maybe (Maybe FilePath)
forall a. a -> Maybe a
Just Maybe FilePath
mainFunIs else Maybe (Maybe FilePath)
forall a. Maybe a
Nothing
                      -- see #5878
        -- pkgopts  = (homeUnit dflags, sort $ packageFlags dflags)
        safeHs :: IfaceTrustInfo
safeHs   = SafeHaskellMode -> IfaceTrustInfo
setSafeMode SafeHaskellMode
safeHaskell
        -- oflags   = sort $ filter filterOFlags $ flags dflags

        -- *all* the extension flags and the language
        lang :: (Maybe Int, [Int])
lang = ((Language -> Int) -> Maybe Language -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Language -> Int
forall a. Enum a => a -> Int
fromEnum Maybe Language
language,
                (Extension -> Int) -> [Extension] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Extension -> Int
forall a. Enum a => a -> Int
fromEnum ([Extension] -> [Int]) -> [Extension] -> [Int]
forall a b. (a -> b) -> a -> b
$ EnumSet Extension -> [Extension]
forall a. Enum a => EnumSet a -> [a]
EnumSet.toList EnumSet Extension
extensionFlags)

        -- -I, -D and -U flags affect CPP
        cpp :: ([FilePath], [FilePath], ([FilePath], Fingerprint))
cpp = ( (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath
normalise ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ IncludeSpecs -> [FilePath]
flattenIncludes IncludeSpecs
includePaths
            -- normalise: eliminate spurious differences due to "./foo" vs "foo"
              , DynFlags -> [FilePath]
picPOpts DynFlags
dflags
              , DynFlags -> ([FilePath], Fingerprint)
opt_P_signature DynFlags
dflags)
            -- See Note [Repeated -optP hashing]

        -- Note [path flags and recompilation]
        paths :: [FilePath]
paths = [ FilePath
hcSuf ]

        -- -fprof-auto etc.
        prof :: Int
prof = if DynFlags -> Bool
sccProfilingEnabled DynFlags
dflags then ProfAuto -> Int
forall a. Enum a => a -> Int
fromEnum ProfAuto
profAuto else Int
0

        -- Ticky
        ticky :: [Bool]
ticky =
          (GeneralFlag -> Bool) -> [GeneralFlag] -> [Bool]
forall a b. (a -> b) -> [a] -> [b]
map (GeneralFlag -> DynFlags -> Bool
`gopt` DynFlags
dflags) [GeneralFlag
Opt_Ticky, GeneralFlag
Opt_Ticky_Allocd, GeneralFlag
Opt_Ticky_LNE, GeneralFlag
Opt_Ticky_Dyn_Thunk]

        flags :: ((Maybe (Maybe FilePath), IfaceTrustInfo, (Maybe Int, [Int]),
  ([FilePath], [FilePath], ([FilePath], Fingerprint))),
 ([FilePath], Int, [Bool], Int))
flags = ((Maybe (Maybe FilePath)
mainis, IfaceTrustInfo
safeHs, (Maybe Int, [Int])
lang, ([FilePath], [FilePath], ([FilePath], Fingerprint))
cpp), ([FilePath]
paths, Int
prof, [Bool]
ticky, Int
debugLevel))

    in -- pprTrace "flags" (ppr flags) $
       (BinHandle -> Name -> IO ())
-> ((Maybe (Maybe FilePath), IfaceTrustInfo, (Maybe Int, [Int]),
     ([FilePath], [FilePath], ([FilePath], Fingerprint))),
    ([FilePath], Int, [Bool], Int))
-> IO Fingerprint
forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint BinHandle -> Name -> IO ()
nameio ((Maybe (Maybe FilePath), IfaceTrustInfo, (Maybe Int, [Int]),
  ([FilePath], [FilePath], ([FilePath], Fingerprint))),
 ([FilePath], Int, [Bool], Int))
flags

-- Fingerprint the optimisation info. We keep this separate from the rest of
-- the flags because GHCi users (especially) may wish to ignore changes in
-- optimisation level or optimisation flags so as to use as many pre-existing
-- object files as they can.
-- See Note [Ignoring some flag changes]
fingerprintOptFlags :: DynFlags
                      -> (BinHandle -> Name -> IO ())
                      -> IO Fingerprint
fingerprintOptFlags :: DynFlags -> (BinHandle -> Name -> IO ()) -> IO Fingerprint
fingerprintOptFlags DynFlags{Bool
Int
FilePath
[Int]
[FilePath]
[(FilePath, FilePath)]
[(ModuleName, FilePath)]
[(ModuleName, Module)]
[ModuleName]
[IgnorePackageFlag]
[PackageDBFlag]
[PackageFlag]
[TrustFlag]
[Option]
[OnOff Extension]
[LoadedPlugin]
[StaticPlugin]
Maybe Int
Maybe FilePath
Maybe [UnitDatabase UnitId]
Maybe (FilePath, Int)
Maybe IndefUnitId
Maybe Language
Maybe SseVersion
Maybe BmiVersion
Word
IORef Bool
IORef Int
IORef (Maybe CompilerInfo)
IORef (Maybe LinkerInfo)
IORef (Map FilePath FilePath)
IORef (Set FilePath)
IORef (ModuleEnv Int)
IORef FilesToClean
Set Way
SrcSpan
UnitState
Module
UnitId
Platform
IntWithInf
OverridingBool
Scheme
SafeHaskellMode
HscTarget
CfgWeights
DynLibLoader
FlushErr
FlushOut
GhcLink
GhcMode
IncludeSpecs
LlvmConfig
ProfAuto
RtsOptsEnabled
PlatformMisc
FileSettings
GhcNameVersion
PlatformConstants
ToolSettings
Hooks
EnumSet Extension
EnumSet DumpFlag
EnumSet GeneralFlag
EnumSet WarningFlag
DumpAction
LogAction
TraceAction
cfgWeightInfo :: CfgWeights
uniqueIncrement :: Int
initialUnique :: Int
maxErrors :: Maybe Int
reverseErrors :: Bool
maxInlineMemsetInsns :: Int
maxInlineMemcpyInsns :: Int
maxInlineAllocSize :: Int
rtccInfo :: IORef (Maybe CompilerInfo)
rtldInfo :: IORef (Maybe LinkerInfo)
avx512pf :: Bool
avx512f :: Bool
avx512er :: Bool
avx512cd :: Bool
avx2 :: Bool
avx :: Bool
bmiVersion :: Maybe BmiVersion
sseVersion :: Maybe SseVersion
nextWrapperNum :: IORef (ModuleEnv Int)
interactivePrint :: Maybe FilePath
profAuto :: ProfAuto
colScheme :: Scheme
canUseColor :: Bool
useColor :: OverridingBool
useUnicode :: Bool
pprCols :: Int
pprUserLength :: Int
ghciScripts :: [FilePath]
haddockOptions :: Maybe FilePath
ghcVersionFile :: Maybe FilePath
flushErr :: FlushErr
flushOut :: FlushOut
trace_action :: TraceAction
dump_action :: DumpAction
log_action :: LogAction
ghciHistSize :: Int
maxWorkerArgs :: Int
ufVeryAggressive :: Bool
ufDearOp :: Int
ufDictDiscount :: Int
ufFunAppDiscount :: Int
ufUseThreshold :: Int
ufCreationThreshold :: Int
extensionFlags :: EnumSet Extension
extensions :: [OnOff Extension]
trustworthyOnLoc :: SrcSpan
warnUnsafeOnLoc :: SrcSpan
warnSafeOnLoc :: SrcSpan
pkgTrustOnLoc :: SrcSpan
incoherentOnLoc :: SrcSpan
overlapInstLoc :: SrcSpan
newDerivOnLoc :: SrcSpan
thOnLoc :: SrcSpan
safeInferred :: Bool
safeInfer :: Bool
safeHaskell :: SafeHaskellMode
language :: Maybe Language
fatalWarningFlags :: EnumSet WarningFlag
warningFlags :: EnumSet WarningFlag
generalFlags :: EnumSet GeneralFlag
dumpFlags :: EnumSet DumpFlag
generatedDumps :: IORef (Set FilePath)
nextTempSuffix :: IORef Int
dirsToClean :: IORef (Map FilePath FilePath)
filesToClean :: IORef FilesToClean
unitState :: UnitState
unitDatabases :: Maybe [UnitDatabase UnitId]
packageEnv :: Maybe FilePath
trustFlags :: [TrustFlag]
pluginPackageFlags :: [PackageFlag]
packageFlags :: [PackageFlag]
ignorePackageFlags :: [IgnorePackageFlag]
packageDBFlags :: [PackageDBFlag]
depSuffixes :: [FilePath]
depExcludeMods :: [ModuleName]
depIncludeCppDeps :: Bool
depIncludePkgDeps :: Bool
depMakefile :: FilePath
hooks :: Hooks
staticPlugins :: [StaticPlugin]
cachedPlugins :: [LoadedPlugin]
frontendPluginOpts :: [FilePath]
pluginModNameOpts :: [(ModuleName, FilePath)]
pluginModNames :: [ModuleName]
hpcDir :: FilePath
rtsOptsSuggestions :: Bool
rtsOptsEnabled :: RtsOptsEnabled
rtsOpts :: Maybe FilePath
cmdlineFrameworks :: [FilePath]
frameworkPaths :: [FilePath]
libraryPaths :: [FilePath]
includePaths :: IncludeSpecs
ldInputs :: [Option]
dumpPrefixForce :: Maybe FilePath
dumpPrefix :: Maybe FilePath
dynLibLoader :: DynLibLoader
outputHi :: Maybe FilePath
dynOutputFile :: Maybe FilePath
outputFile :: Maybe FilePath
dynHiSuf :: FilePath
dynObjectSuf :: FilePath
canGenerateDynamicToo :: IORef Bool
hieSuf :: FilePath
hiSuf :: FilePath
hcSuf :: FilePath
objectSuf :: FilePath
dumpDir :: Maybe FilePath
stubDir :: Maybe FilePath
hieDir :: Maybe FilePath
hiDir :: Maybe FilePath
dylibInstallName :: Maybe FilePath
objectDir :: Maybe FilePath
splitInfo :: Maybe (FilePath, Int)
ways :: Set Way
homeUnitInstantiations :: [(ModuleName, Module)]
homeUnitInstanceOfId :: Maybe IndefUnitId
homeUnitId :: UnitId
solverIterations :: IntWithInf
reductionDepth :: IntWithInf
mainFunIs :: Maybe FilePath
mainModIs :: Module
importPaths :: [FilePath]
historySize :: Int
cmmProcAlignment :: Maybe Int
liftLamsKnown :: Bool
liftLamsNonRecArgs :: Maybe Int
liftLamsRecArgs :: Maybe Int
floatLamArgs :: Maybe Int
liberateCaseThreshold :: Maybe Int
binBlobThreshold :: Word
specConstrRecursive :: Int
specConstrCount :: Maybe Int
specConstrThreshold :: Maybe Int
simplTickFactor :: Int
maxPmCheckModels :: Int
maxUncoveredPatterns :: Int
refLevelHoleFits :: Maybe Int
maxRefHoleFits :: Maybe Int
maxValidHoleFits :: Maybe Int
maxRelevantBinds :: Maybe Int
ghcHeapSize :: Maybe Int
enableTimeStats :: Bool
parMakeCount :: Maybe Int
strictnessBefore :: [Int]
inlineCheck :: Maybe FilePath
ruleCheck :: Maybe FilePath
maxSimplIterations :: Int
simplPhases :: Int
debugLevel :: Int
optLevel :: Int
verbosity :: Int
llvmConfig :: LlvmConfig
rawSettings :: [(FilePath, FilePath)]
platformConstants :: PlatformConstants
platformMisc :: PlatformMisc
toolSettings :: ToolSettings
targetPlatform :: Platform
fileSettings :: FileSettings
ghcNameVersion :: GhcNameVersion
hscTarget :: HscTarget
ghcLink :: GhcLink
ghcMode :: GhcMode
ways :: DynFlags -> Set Way
warningFlags :: DynFlags -> EnumSet WarningFlag
warnUnsafeOnLoc :: DynFlags -> SrcSpan
warnSafeOnLoc :: DynFlags -> SrcSpan
verbosity :: DynFlags -> Int
useUnicode :: DynFlags -> Bool
useColor :: DynFlags -> OverridingBool
unitState :: DynFlags -> UnitState
unitDatabases :: DynFlags -> Maybe [UnitDatabase UnitId]
uniqueIncrement :: DynFlags -> Int
ufVeryAggressive :: DynFlags -> Bool
ufUseThreshold :: DynFlags -> Int
ufFunAppDiscount :: DynFlags -> Int
ufDictDiscount :: DynFlags -> Int
ufDearOp :: DynFlags -> Int
ufCreationThreshold :: DynFlags -> Int
trustworthyOnLoc :: DynFlags -> SrcSpan
trustFlags :: DynFlags -> [TrustFlag]
trace_action :: DynFlags -> TraceAction
toolSettings :: DynFlags -> ToolSettings
thOnLoc :: DynFlags -> SrcSpan
targetPlatform :: DynFlags -> Platform
stubDir :: DynFlags -> Maybe FilePath
strictnessBefore :: DynFlags -> [Int]
staticPlugins :: DynFlags -> [StaticPlugin]
sseVersion :: DynFlags -> Maybe SseVersion
splitInfo :: DynFlags -> Maybe (FilePath, Int)
specConstrThreshold :: DynFlags -> Maybe Int
specConstrRecursive :: DynFlags -> Int
specConstrCount :: DynFlags -> Maybe Int
solverIterations :: DynFlags -> IntWithInf
simplTickFactor :: DynFlags -> Int
simplPhases :: DynFlags -> Int
safeInferred :: DynFlags -> Bool
safeInfer :: DynFlags -> Bool
safeHaskell :: DynFlags -> SafeHaskellMode
ruleCheck :: DynFlags -> Maybe FilePath
rtsOptsSuggestions :: DynFlags -> Bool
rtsOptsEnabled :: DynFlags -> RtsOptsEnabled
rtsOpts :: DynFlags -> Maybe FilePath
rtldInfo :: DynFlags -> IORef (Maybe LinkerInfo)
rtccInfo :: DynFlags -> IORef (Maybe CompilerInfo)
reverseErrors :: DynFlags -> Bool
refLevelHoleFits :: DynFlags -> Maybe Int
reductionDepth :: DynFlags -> IntWithInf
rawSettings :: DynFlags -> [(FilePath, FilePath)]
profAuto :: DynFlags -> ProfAuto
pprUserLength :: DynFlags -> Int
pprCols :: DynFlags -> Int
pluginPackageFlags :: DynFlags -> [PackageFlag]
pluginModNames :: DynFlags -> [ModuleName]
pluginModNameOpts :: DynFlags -> [(ModuleName, FilePath)]
platformMisc :: DynFlags -> PlatformMisc
platformConstants :: DynFlags -> PlatformConstants
pkgTrustOnLoc :: DynFlags -> SrcSpan
parMakeCount :: DynFlags -> Maybe Int
packageFlags :: DynFlags -> [PackageFlag]
packageEnv :: DynFlags -> Maybe FilePath
packageDBFlags :: DynFlags -> [PackageDBFlag]
overlapInstLoc :: DynFlags -> SrcSpan
outputHi :: DynFlags -> Maybe FilePath
outputFile :: DynFlags -> Maybe FilePath
optLevel :: DynFlags -> Int
objectSuf :: DynFlags -> FilePath
objectDir :: DynFlags -> Maybe FilePath
nextWrapperNum :: DynFlags -> IORef (ModuleEnv Int)
nextTempSuffix :: DynFlags -> IORef Int
newDerivOnLoc :: DynFlags -> SrcSpan
maxWorkerArgs :: DynFlags -> Int
maxValidHoleFits :: DynFlags -> Maybe Int
maxUncoveredPatterns :: DynFlags -> Int
maxSimplIterations :: DynFlags -> Int
maxRelevantBinds :: DynFlags -> Maybe Int
maxRefHoleFits :: DynFlags -> Maybe Int
maxPmCheckModels :: DynFlags -> Int
maxInlineMemsetInsns :: DynFlags -> Int
maxInlineMemcpyInsns :: DynFlags -> Int
maxInlineAllocSize :: DynFlags -> Int
maxErrors :: DynFlags -> Maybe Int
mainModIs :: DynFlags -> Module
mainFunIs :: DynFlags -> Maybe FilePath
log_action :: DynFlags -> LogAction
llvmConfig :: DynFlags -> LlvmConfig
liftLamsRecArgs :: DynFlags -> Maybe Int
liftLamsNonRecArgs :: DynFlags -> Maybe Int
liftLamsKnown :: DynFlags -> Bool
libraryPaths :: DynFlags -> [FilePath]
liberateCaseThreshold :: DynFlags -> Maybe Int
ldInputs :: DynFlags -> [Option]
language :: DynFlags -> Maybe Language
interactivePrint :: DynFlags -> Maybe FilePath
inlineCheck :: DynFlags -> Maybe FilePath
initialUnique :: DynFlags -> Int
incoherentOnLoc :: DynFlags -> SrcSpan
includePaths :: DynFlags -> IncludeSpecs
importPaths :: DynFlags -> [FilePath]
ignorePackageFlags :: DynFlags -> [IgnorePackageFlag]
hscTarget :: DynFlags -> HscTarget
hpcDir :: DynFlags -> FilePath
hooks :: DynFlags -> Hooks
homeUnitInstantiations :: DynFlags -> [(ModuleName, Module)]
homeUnitInstanceOfId :: DynFlags -> Maybe IndefUnitId
homeUnitId :: DynFlags -> UnitId
historySize :: DynFlags -> Int
hieSuf :: DynFlags -> FilePath
hieDir :: DynFlags -> Maybe FilePath
hiSuf :: DynFlags -> FilePath
hiDir :: DynFlags -> Maybe FilePath
hcSuf :: DynFlags -> FilePath
haddockOptions :: DynFlags -> Maybe FilePath
ghciScripts :: DynFlags -> [FilePath]
ghciHistSize :: DynFlags -> Int
ghcVersionFile :: DynFlags -> Maybe FilePath
ghcNameVersion :: DynFlags -> GhcNameVersion
ghcMode :: DynFlags -> GhcMode
ghcLink :: DynFlags -> GhcLink
ghcHeapSize :: DynFlags -> Maybe Int
generatedDumps :: DynFlags -> IORef (Set FilePath)
generalFlags :: DynFlags -> EnumSet GeneralFlag
frontendPluginOpts :: DynFlags -> [FilePath]
frameworkPaths :: DynFlags -> [FilePath]
flushOut :: DynFlags -> FlushOut
flushErr :: DynFlags -> FlushErr
floatLamArgs :: DynFlags -> Maybe Int
filesToClean :: DynFlags -> IORef FilesToClean
fileSettings :: DynFlags -> FileSettings
fatalWarningFlags :: DynFlags -> EnumSet WarningFlag
extensions :: DynFlags -> [OnOff Extension]
extensionFlags :: DynFlags -> EnumSet Extension
enableTimeStats :: DynFlags -> Bool
dynOutputFile :: DynFlags -> Maybe FilePath
dynObjectSuf :: DynFlags -> FilePath
dynLibLoader :: DynFlags -> DynLibLoader
dynHiSuf :: DynFlags -> FilePath
dylibInstallName :: DynFlags -> Maybe FilePath
dump_action :: DynFlags -> DumpAction
dumpPrefixForce :: DynFlags -> Maybe FilePath
dumpPrefix :: DynFlags -> Maybe FilePath
dumpFlags :: DynFlags -> EnumSet DumpFlag
dumpDir :: DynFlags -> Maybe FilePath
dirsToClean :: DynFlags -> IORef (Map FilePath FilePath)
depSuffixes :: DynFlags -> [FilePath]
depMakefile :: DynFlags -> FilePath
depIncludePkgDeps :: DynFlags -> Bool
depIncludeCppDeps :: DynFlags -> Bool
depExcludeMods :: DynFlags -> [ModuleName]
debugLevel :: DynFlags -> Int
colScheme :: DynFlags -> Scheme
cmmProcAlignment :: DynFlags -> Maybe Int
cmdlineFrameworks :: DynFlags -> [FilePath]
cfgWeightInfo :: DynFlags -> CfgWeights
canUseColor :: DynFlags -> Bool
canGenerateDynamicToo :: DynFlags -> IORef Bool
cachedPlugins :: DynFlags -> [LoadedPlugin]
bmiVersion :: DynFlags -> Maybe BmiVersion
binBlobThreshold :: DynFlags -> Word
avx512pf :: DynFlags -> Bool
avx512f :: DynFlags -> Bool
avx512er :: DynFlags -> Bool
avx512cd :: DynFlags -> Bool
avx2 :: DynFlags -> Bool
avx :: DynFlags -> Bool
..} BinHandle -> Name -> IO ()
nameio =
      let
        -- See https://gitlab.haskell.org/ghc/ghc/issues/10923
        -- We used to fingerprint the optimisation level, but as Joachim
        -- Breitner pointed out in comment 9 on that ticket, it's better
        -- to ignore that and just look at the individual optimisation flags.
        opt_flags :: [Int]
opt_flags = (GeneralFlag -> Int) -> [GeneralFlag] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map GeneralFlag -> Int
forall a. Enum a => a -> Int
fromEnum ([GeneralFlag] -> [Int]) -> [GeneralFlag] -> [Int]
forall a b. (a -> b) -> a -> b
$ (GeneralFlag -> Bool) -> [GeneralFlag] -> [GeneralFlag]
forall a. (a -> Bool) -> [a] -> [a]
filter (GeneralFlag -> EnumSet GeneralFlag -> Bool
forall a. Enum a => a -> EnumSet a -> Bool
`EnumSet.member` EnumSet GeneralFlag
optimisationFlags)
                                          (EnumSet GeneralFlag -> [GeneralFlag]
forall a. Enum a => EnumSet a -> [a]
EnumSet.toList EnumSet GeneralFlag
generalFlags)

      in (BinHandle -> Name -> IO ()) -> [Int] -> IO Fingerprint
forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint BinHandle -> Name -> IO ()
nameio [Int]
opt_flags

-- Fingerprint the HPC info. We keep this separate from the rest of
-- the flags because GHCi users (especially) may wish to use an object
-- file compiled for HPC when not actually using HPC.
-- See Note [Ignoring some flag changes]
fingerprintHpcFlags :: DynFlags
                      -> (BinHandle -> Name -> IO ())
                      -> IO Fingerprint
fingerprintHpcFlags :: DynFlags -> (BinHandle -> Name -> IO ()) -> IO Fingerprint
fingerprintHpcFlags dflags :: DynFlags
dflags@DynFlags{Bool
Int
FilePath
[Int]
[FilePath]
[(FilePath, FilePath)]
[(ModuleName, FilePath)]
[(ModuleName, Module)]
[ModuleName]
[IgnorePackageFlag]
[PackageDBFlag]
[PackageFlag]
[TrustFlag]
[Option]
[OnOff Extension]
[LoadedPlugin]
[StaticPlugin]
Maybe Int
Maybe FilePath
Maybe [UnitDatabase UnitId]
Maybe (FilePath, Int)
Maybe IndefUnitId
Maybe Language
Maybe SseVersion
Maybe BmiVersion
Word
IORef Bool
IORef Int
IORef (Maybe CompilerInfo)
IORef (Maybe LinkerInfo)
IORef (Map FilePath FilePath)
IORef (Set FilePath)
IORef (ModuleEnv Int)
IORef FilesToClean
Set Way
SrcSpan
UnitState
Module
UnitId
Platform
IntWithInf
OverridingBool
Scheme
SafeHaskellMode
HscTarget
CfgWeights
DynLibLoader
FlushErr
FlushOut
GhcLink
GhcMode
IncludeSpecs
LlvmConfig
ProfAuto
RtsOptsEnabled
PlatformMisc
FileSettings
GhcNameVersion
PlatformConstants
ToolSettings
Hooks
EnumSet Extension
EnumSet DumpFlag
EnumSet GeneralFlag
EnumSet WarningFlag
DumpAction
LogAction
TraceAction
cfgWeightInfo :: CfgWeights
uniqueIncrement :: Int
initialUnique :: Int
maxErrors :: Maybe Int
reverseErrors :: Bool
maxInlineMemsetInsns :: Int
maxInlineMemcpyInsns :: Int
maxInlineAllocSize :: Int
rtccInfo :: IORef (Maybe CompilerInfo)
rtldInfo :: IORef (Maybe LinkerInfo)
avx512pf :: Bool
avx512f :: Bool
avx512er :: Bool
avx512cd :: Bool
avx2 :: Bool
avx :: Bool
bmiVersion :: Maybe BmiVersion
sseVersion :: Maybe SseVersion
nextWrapperNum :: IORef (ModuleEnv Int)
interactivePrint :: Maybe FilePath
profAuto :: ProfAuto
colScheme :: Scheme
canUseColor :: Bool
useColor :: OverridingBool
useUnicode :: Bool
pprCols :: Int
pprUserLength :: Int
ghciScripts :: [FilePath]
haddockOptions :: Maybe FilePath
ghcVersionFile :: Maybe FilePath
flushErr :: FlushErr
flushOut :: FlushOut
trace_action :: TraceAction
dump_action :: DumpAction
log_action :: LogAction
ghciHistSize :: Int
maxWorkerArgs :: Int
ufVeryAggressive :: Bool
ufDearOp :: Int
ufDictDiscount :: Int
ufFunAppDiscount :: Int
ufUseThreshold :: Int
ufCreationThreshold :: Int
extensionFlags :: EnumSet Extension
extensions :: [OnOff Extension]
trustworthyOnLoc :: SrcSpan
warnUnsafeOnLoc :: SrcSpan
warnSafeOnLoc :: SrcSpan
pkgTrustOnLoc :: SrcSpan
incoherentOnLoc :: SrcSpan
overlapInstLoc :: SrcSpan
newDerivOnLoc :: SrcSpan
thOnLoc :: SrcSpan
safeInferred :: Bool
safeInfer :: Bool
safeHaskell :: SafeHaskellMode
language :: Maybe Language
fatalWarningFlags :: EnumSet WarningFlag
warningFlags :: EnumSet WarningFlag
generalFlags :: EnumSet GeneralFlag
dumpFlags :: EnumSet DumpFlag
generatedDumps :: IORef (Set FilePath)
nextTempSuffix :: IORef Int
dirsToClean :: IORef (Map FilePath FilePath)
filesToClean :: IORef FilesToClean
unitState :: UnitState
unitDatabases :: Maybe [UnitDatabase UnitId]
packageEnv :: Maybe FilePath
trustFlags :: [TrustFlag]
pluginPackageFlags :: [PackageFlag]
packageFlags :: [PackageFlag]
ignorePackageFlags :: [IgnorePackageFlag]
packageDBFlags :: [PackageDBFlag]
depSuffixes :: [FilePath]
depExcludeMods :: [ModuleName]
depIncludeCppDeps :: Bool
depIncludePkgDeps :: Bool
depMakefile :: FilePath
hooks :: Hooks
staticPlugins :: [StaticPlugin]
cachedPlugins :: [LoadedPlugin]
frontendPluginOpts :: [FilePath]
pluginModNameOpts :: [(ModuleName, FilePath)]
pluginModNames :: [ModuleName]
hpcDir :: FilePath
rtsOptsSuggestions :: Bool
rtsOptsEnabled :: RtsOptsEnabled
rtsOpts :: Maybe FilePath
cmdlineFrameworks :: [FilePath]
frameworkPaths :: [FilePath]
libraryPaths :: [FilePath]
includePaths :: IncludeSpecs
ldInputs :: [Option]
dumpPrefixForce :: Maybe FilePath
dumpPrefix :: Maybe FilePath
dynLibLoader :: DynLibLoader
outputHi :: Maybe FilePath
dynOutputFile :: Maybe FilePath
outputFile :: Maybe FilePath
dynHiSuf :: FilePath
dynObjectSuf :: FilePath
canGenerateDynamicToo :: IORef Bool
hieSuf :: FilePath
hiSuf :: FilePath
hcSuf :: FilePath
objectSuf :: FilePath
dumpDir :: Maybe FilePath
stubDir :: Maybe FilePath
hieDir :: Maybe FilePath
hiDir :: Maybe FilePath
dylibInstallName :: Maybe FilePath
objectDir :: Maybe FilePath
splitInfo :: Maybe (FilePath, Int)
ways :: Set Way
homeUnitInstantiations :: [(ModuleName, Module)]
homeUnitInstanceOfId :: Maybe IndefUnitId
homeUnitId :: UnitId
solverIterations :: IntWithInf
reductionDepth :: IntWithInf
mainFunIs :: Maybe FilePath
mainModIs :: Module
importPaths :: [FilePath]
historySize :: Int
cmmProcAlignment :: Maybe Int
liftLamsKnown :: Bool
liftLamsNonRecArgs :: Maybe Int
liftLamsRecArgs :: Maybe Int
floatLamArgs :: Maybe Int
liberateCaseThreshold :: Maybe Int
binBlobThreshold :: Word
specConstrRecursive :: Int
specConstrCount :: Maybe Int
specConstrThreshold :: Maybe Int
simplTickFactor :: Int
maxPmCheckModels :: Int
maxUncoveredPatterns :: Int
refLevelHoleFits :: Maybe Int
maxRefHoleFits :: Maybe Int
maxValidHoleFits :: Maybe Int
maxRelevantBinds :: Maybe Int
ghcHeapSize :: Maybe Int
enableTimeStats :: Bool
parMakeCount :: Maybe Int
strictnessBefore :: [Int]
inlineCheck :: Maybe FilePath
ruleCheck :: Maybe FilePath
maxSimplIterations :: Int
simplPhases :: Int
debugLevel :: Int
optLevel :: Int
verbosity :: Int
llvmConfig :: LlvmConfig
rawSettings :: [(FilePath, FilePath)]
platformConstants :: PlatformConstants
platformMisc :: PlatformMisc
toolSettings :: ToolSettings
targetPlatform :: Platform
fileSettings :: FileSettings
ghcNameVersion :: GhcNameVersion
hscTarget :: HscTarget
ghcLink :: GhcLink
ghcMode :: GhcMode
ways :: DynFlags -> Set Way
warningFlags :: DynFlags -> EnumSet WarningFlag
warnUnsafeOnLoc :: DynFlags -> SrcSpan
warnSafeOnLoc :: DynFlags -> SrcSpan
verbosity :: DynFlags -> Int
useUnicode :: DynFlags -> Bool
useColor :: DynFlags -> OverridingBool
unitState :: DynFlags -> UnitState
unitDatabases :: DynFlags -> Maybe [UnitDatabase UnitId]
uniqueIncrement :: DynFlags -> Int
ufVeryAggressive :: DynFlags -> Bool
ufUseThreshold :: DynFlags -> Int
ufFunAppDiscount :: DynFlags -> Int
ufDictDiscount :: DynFlags -> Int
ufDearOp :: DynFlags -> Int
ufCreationThreshold :: DynFlags -> Int
trustworthyOnLoc :: DynFlags -> SrcSpan
trustFlags :: DynFlags -> [TrustFlag]
trace_action :: DynFlags -> TraceAction
toolSettings :: DynFlags -> ToolSettings
thOnLoc :: DynFlags -> SrcSpan
targetPlatform :: DynFlags -> Platform
stubDir :: DynFlags -> Maybe FilePath
strictnessBefore :: DynFlags -> [Int]
staticPlugins :: DynFlags -> [StaticPlugin]
sseVersion :: DynFlags -> Maybe SseVersion
splitInfo :: DynFlags -> Maybe (FilePath, Int)
specConstrThreshold :: DynFlags -> Maybe Int
specConstrRecursive :: DynFlags -> Int
specConstrCount :: DynFlags -> Maybe Int
solverIterations :: DynFlags -> IntWithInf
simplTickFactor :: DynFlags -> Int
simplPhases :: DynFlags -> Int
safeInferred :: DynFlags -> Bool
safeInfer :: DynFlags -> Bool
safeHaskell :: DynFlags -> SafeHaskellMode
ruleCheck :: DynFlags -> Maybe FilePath
rtsOptsSuggestions :: DynFlags -> Bool
rtsOptsEnabled :: DynFlags -> RtsOptsEnabled
rtsOpts :: DynFlags -> Maybe FilePath
rtldInfo :: DynFlags -> IORef (Maybe LinkerInfo)
rtccInfo :: DynFlags -> IORef (Maybe CompilerInfo)
reverseErrors :: DynFlags -> Bool
refLevelHoleFits :: DynFlags -> Maybe Int
reductionDepth :: DynFlags -> IntWithInf
rawSettings :: DynFlags -> [(FilePath, FilePath)]
profAuto :: DynFlags -> ProfAuto
pprUserLength :: DynFlags -> Int
pprCols :: DynFlags -> Int
pluginPackageFlags :: DynFlags -> [PackageFlag]
pluginModNames :: DynFlags -> [ModuleName]
pluginModNameOpts :: DynFlags -> [(ModuleName, FilePath)]
platformMisc :: DynFlags -> PlatformMisc
platformConstants :: DynFlags -> PlatformConstants
pkgTrustOnLoc :: DynFlags -> SrcSpan
parMakeCount :: DynFlags -> Maybe Int
packageFlags :: DynFlags -> [PackageFlag]
packageEnv :: DynFlags -> Maybe FilePath
packageDBFlags :: DynFlags -> [PackageDBFlag]
overlapInstLoc :: DynFlags -> SrcSpan
outputHi :: DynFlags -> Maybe FilePath
outputFile :: DynFlags -> Maybe FilePath
optLevel :: DynFlags -> Int
objectSuf :: DynFlags -> FilePath
objectDir :: DynFlags -> Maybe FilePath
nextWrapperNum :: DynFlags -> IORef (ModuleEnv Int)
nextTempSuffix :: DynFlags -> IORef Int
newDerivOnLoc :: DynFlags -> SrcSpan
maxWorkerArgs :: DynFlags -> Int
maxValidHoleFits :: DynFlags -> Maybe Int
maxUncoveredPatterns :: DynFlags -> Int
maxSimplIterations :: DynFlags -> Int
maxRelevantBinds :: DynFlags -> Maybe Int
maxRefHoleFits :: DynFlags -> Maybe Int
maxPmCheckModels :: DynFlags -> Int
maxInlineMemsetInsns :: DynFlags -> Int
maxInlineMemcpyInsns :: DynFlags -> Int
maxInlineAllocSize :: DynFlags -> Int
maxErrors :: DynFlags -> Maybe Int
mainModIs :: DynFlags -> Module
mainFunIs :: DynFlags -> Maybe FilePath
log_action :: DynFlags -> LogAction
llvmConfig :: DynFlags -> LlvmConfig
liftLamsRecArgs :: DynFlags -> Maybe Int
liftLamsNonRecArgs :: DynFlags -> Maybe Int
liftLamsKnown :: DynFlags -> Bool
libraryPaths :: DynFlags -> [FilePath]
liberateCaseThreshold :: DynFlags -> Maybe Int
ldInputs :: DynFlags -> [Option]
language :: DynFlags -> Maybe Language
interactivePrint :: DynFlags -> Maybe FilePath
inlineCheck :: DynFlags -> Maybe FilePath
initialUnique :: DynFlags -> Int
incoherentOnLoc :: DynFlags -> SrcSpan
includePaths :: DynFlags -> IncludeSpecs
importPaths :: DynFlags -> [FilePath]
ignorePackageFlags :: DynFlags -> [IgnorePackageFlag]
hscTarget :: DynFlags -> HscTarget
hpcDir :: DynFlags -> FilePath
hooks :: DynFlags -> Hooks
homeUnitInstantiations :: DynFlags -> [(ModuleName, Module)]
homeUnitInstanceOfId :: DynFlags -> Maybe IndefUnitId
homeUnitId :: DynFlags -> UnitId
historySize :: DynFlags -> Int
hieSuf :: DynFlags -> FilePath
hieDir :: DynFlags -> Maybe FilePath
hiSuf :: DynFlags -> FilePath
hiDir :: DynFlags -> Maybe FilePath
hcSuf :: DynFlags -> FilePath
haddockOptions :: DynFlags -> Maybe FilePath
ghciScripts :: DynFlags -> [FilePath]
ghciHistSize :: DynFlags -> Int
ghcVersionFile :: DynFlags -> Maybe FilePath
ghcNameVersion :: DynFlags -> GhcNameVersion
ghcMode :: DynFlags -> GhcMode
ghcLink :: DynFlags -> GhcLink
ghcHeapSize :: DynFlags -> Maybe Int
generatedDumps :: DynFlags -> IORef (Set FilePath)
generalFlags :: DynFlags -> EnumSet GeneralFlag
frontendPluginOpts :: DynFlags -> [FilePath]
frameworkPaths :: DynFlags -> [FilePath]
flushOut :: DynFlags -> FlushOut
flushErr :: DynFlags -> FlushErr
floatLamArgs :: DynFlags -> Maybe Int
filesToClean :: DynFlags -> IORef FilesToClean
fileSettings :: DynFlags -> FileSettings
fatalWarningFlags :: DynFlags -> EnumSet WarningFlag
extensions :: DynFlags -> [OnOff Extension]
extensionFlags :: DynFlags -> EnumSet Extension
enableTimeStats :: DynFlags -> Bool
dynOutputFile :: DynFlags -> Maybe FilePath
dynObjectSuf :: DynFlags -> FilePath
dynLibLoader :: DynFlags -> DynLibLoader
dynHiSuf :: DynFlags -> FilePath
dylibInstallName :: DynFlags -> Maybe FilePath
dump_action :: DynFlags -> DumpAction
dumpPrefixForce :: DynFlags -> Maybe FilePath
dumpPrefix :: DynFlags -> Maybe FilePath
dumpFlags :: DynFlags -> EnumSet DumpFlag
dumpDir :: DynFlags -> Maybe FilePath
dirsToClean :: DynFlags -> IORef (Map FilePath FilePath)
depSuffixes :: DynFlags -> [FilePath]
depMakefile :: DynFlags -> FilePath
depIncludePkgDeps :: DynFlags -> Bool
depIncludeCppDeps :: DynFlags -> Bool
depExcludeMods :: DynFlags -> [ModuleName]
debugLevel :: DynFlags -> Int
colScheme :: DynFlags -> Scheme
cmmProcAlignment :: DynFlags -> Maybe Int
cmdlineFrameworks :: DynFlags -> [FilePath]
cfgWeightInfo :: DynFlags -> CfgWeights
canUseColor :: DynFlags -> Bool
canGenerateDynamicToo :: DynFlags -> IORef Bool
cachedPlugins :: DynFlags -> [LoadedPlugin]
bmiVersion :: DynFlags -> Maybe BmiVersion
binBlobThreshold :: DynFlags -> Word
avx512pf :: DynFlags -> Bool
avx512f :: DynFlags -> Bool
avx512er :: DynFlags -> Bool
avx512cd :: DynFlags -> Bool
avx2 :: DynFlags -> Bool
avx :: DynFlags -> Bool
..} BinHandle -> Name -> IO ()
nameio =
      let
        -- -fhpc, see https://gitlab.haskell.org/ghc/ghc/issues/11798
        -- hpcDir is output-only, so we should recompile if it changes
        hpc :: Maybe FilePath
hpc = if GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_Hpc DynFlags
dflags then FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
hpcDir else Maybe FilePath
forall a. Maybe a
Nothing

      in (BinHandle -> Name -> IO ()) -> Maybe FilePath -> IO Fingerprint
forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint BinHandle -> Name -> IO ()
nameio Maybe FilePath
hpc


{- Note [path flags and recompilation]

There are several flags that we deliberately omit from the
recompilation check; here we explain why.

-osuf, -odir, -hisuf, -hidir
  If GHC decides that it does not need to recompile, then
  it must have found an up-to-date .hi file and .o file.
  There is no point recording these flags - the user must
  have passed the correct ones.  Indeed, the user may
  have compiled the source file in one-shot mode using
  -o to specify the .o file, and then loaded it in GHCi
  using -odir.

-stubdir
  We omit this one because it is automatically set by -outputdir, and
  we don't want changes in -outputdir to automatically trigger
  recompilation.  This could be wrong, but only in very rare cases.

-i (importPaths)
  For the same reason as -osuf etc. above: if GHC decides not to
  recompile, then it must have already checked all the .hi files on
  which the current module depends, so it must have found them
  successfully.  It is occasionally useful to be able to cd to a
  different directory and use -i flags to enable GHC to find the .hi
  files; we don't want this to force recompilation.

The only path-related flag left is -hcsuf.
-}

{- Note [Ignoring some flag changes]
   ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

Normally, --make tries to reuse only compilation products that are
the same as those that would have been produced compiling from
scratch. Sometimes, however, users would like to be more aggressive
about recompilation avoidance. This is particularly likely when
developing using GHCi (see #13604). Currently, we allow users to
ignore optimisation changes using -fignore-optim-changes, and to
ignore HPC option changes using -fignore-hpc-changes. If there's a
demand for it, we could also allow changes to -fprof-auto-* flags
(although we can't allow -prof flags to differ). The key thing about
these options is that we can still successfully link a library or
executable when some of its components differ in these ways.

The way we accomplish this is to leave the optimization and HPC
options out of the flag hash, hashing them separately.
-}

{- Note [Repeated -optP hashing]
   ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

We invoke fingerprintDynFlags for each compiled module to include
the hash of relevant DynFlags in the resulting interface file.
-optP (preprocessor) flags are part of that hash.
-optP flags can come from multiple places:

  1. -optP flags directly passed on command line.
  2. -optP flags implied by other flags. Eg. -DPROFILING implied by -prof.
  3. -optP flags added with {-# OPTIONS -optP-D__F__ #-} in a file.

When compiling many modules at once with many -optP command line arguments
the work of hashing -optP flags would be repeated. This can get expensive
and as noted on #14697 it can take 7% of time and 14% of allocations on
a real codebase.

The obvious solution is to cache the hash of -optP flags per GHC invocation.
However, one has to be careful there, as the flags that were added in 3. way
have to be accounted for.

The current strategy is as follows:

  1. Lazily compute the hash of sOpt_p in sOpt_P_fingerprint whenever sOpt_p
     is modified. This serves dual purpose. It ensures correctness for when
     we add per file -optP flags and lets us save work for when we don't.
  2. When computing the fingerprint in fingerprintDynFlags use the cached
     value *and* fingerprint the additional implied (see 2. above) -optP flags.
     This is relatively cheap and saves the headache of fingerprinting all
     the -optP flags and tracking all the places that could invalidate the
     cache.
-}