summaryrefslogtreecommitdiff
path: root/compiler/GHC/Iface/Recomp/Flags.hs
blob: 024320f6795ba1d26b04b069ab38dcfe4174b573 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
{-# 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 Data.Bifunctor (first)
import GHC.Prelude

import GHC.Driver.Session
import GHC.Driver.Env

import GHC.Utils.Binary
import GHC.Unit.Module
import GHC.Types.Name
import GHC.Types.SafeHaskell
import GHC.Utils.Fingerprint
import GHC.Iface.Recomp.Binary
import GHC.Core.Opt.CallerCC () -- for Binary instances

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 :: HscEnv -> Module
                    -> (BinHandle -> Name -> IO ())
                    -> IO Fingerprint

fingerprintDynFlags hsc_env this_mod nameio =
    let dflags@DynFlags{..} = hsc_dflags hsc_env
        serialisableString = map SerialisableChar
        mainis   = if mainModIs (hsc_HUE hsc_env) == this_mod then Just (fmap serialisableString mainFunIs) else Nothing
                      -- see #5878
        -- pkgopts  = (homeUnit home_unit, sort $ packageFlags dflags)
        safeHs   = setSafeMode safeHaskell
        -- oflags   = sort $ filter filterOFlags $ flags dflags

        -- all the extension flags and the language
        lang = (fmap fromEnum language,
                map fromEnum $ EnumSet.toList extensionFlags)

        -- avoid fingerprinting the absolute path to the directory of the source file
        -- see Note [Implicit include paths]
        includePathsMinusImplicit = includePaths { includePathsQuoteImplicit = [] }

        -- -I, -D and -U flags affect CPP
        cpp = ( map (serialisableString . normalise) $ flattenIncludes includePathsMinusImplicit
            -- normalise: eliminate spurious differences due to "./foo" vs "foo"
              , map serialisableString $ picPOpts dflags
              , first (map serialisableString) $ opt_P_signature dflags)
            -- See Note [Repeated -optP hashing]

        -- Note [path flags and recompilation]
        paths = map serialisableString [ hcSuf ]

        -- -fprof-auto etc.
        prof = if sccProfilingEnabled dflags then fromEnum profAuto else 0

        -- Ticky
        ticky =
          map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk, Opt_Ticky_Tag]

        flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel, callerCcFilters))

    in -- pprTrace "flags" (ppr flags) $
       computeFingerprint nameio 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{..} 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 = map fromEnum $ filter (`EnumSet.member` optimisationFlags)
                                          (EnumSet.toList generalFlags)

      in computeFingerprint nameio 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 dflags@DynFlags{..} nameio =
      let
        -- -fhpc, see https://gitlab.haskell.org/ghc/ghc/issues/11798
        -- hpcDir is output-only, so we should recompile if it changes
        hpc = if gopt Opt_Hpc dflags then Just (map SerialisableChar hpcDir) else Nothing

      in computeFingerprint nameio 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.
-}