{-# LANGUAGE RecordWildCards #-} -- | This module manages storing the various GHC option flags in a modules -- interface file as part of the recompilation checking infrastructure. module FlagChecker ( fingerprintDynFlags , fingerprintOptFlags , fingerprintHpcFlags ) where import GhcPrelude import Binary import BinIface () import DynFlags import HscTypes import Module import Name import Fingerprint import BinFingerprint -- import Outputable import qualified 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{..} this_mod :: Module this_mod nameio :: 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 = (thisPackage 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 GeneralFlag -> DynFlags -> Bool gopt GeneralFlag Opt_SccProfilingOn DynFlags dflags then ProfAuto -> Int forall a. Enum a => a -> Int fromEnum ProfAuto profAuto else 0 flags :: (Maybe (Maybe FilePath), IfaceTrustInfo, (Maybe Int, [Int]), ([FilePath], [FilePath], ([FilePath], Fingerprint)), [FilePath], Int) flags = (Maybe (Maybe FilePath) mainis, IfaceTrustInfo safeHs, (Maybe Int, [Int]) lang, ([FilePath], [FilePath], ([FilePath], Fingerprint)) cpp, [FilePath] paths, Int prof) in -- pprTrace "flags" (ppr flags) $ (BinHandle -> Name -> IO ()) -> (Maybe (Maybe FilePath), IfaceTrustInfo, (Maybe Int, [Int]), ([FilePath], [FilePath], ([FilePath], Fingerprint)), [FilePath], 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) 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{..} nameio :: BinHandle -> Name -> IO () nameio = let -- See https://ghc.haskell.org/trac/ghc/ticket/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{..} nameio :: BinHandle -> Name -> IO () nameio = let -- -fhpc, see https://ghc.haskell.org/trac/ghc/ticket/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. -}