summaryrefslogtreecommitdiff
path: root/compiler/GHC/Iface
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2020-04-05 17:39:13 +0200
committerSylvain Henry <sylvain@haskus.fr>2020-04-18 20:04:46 +0200
commit15312bbb53f247c9ed2c5cf75100a9f44c1c7227 (patch)
tree8306dcc04a5b7c82464f903044dfdd589e7fdcd7 /compiler/GHC/Iface
parent3ca52151881451ce5b3a7740d003e811b586140d (diff)
downloadhaskell-15312bbb53f247c9ed2c5cf75100a9f44c1c7227.tar.gz
Modules (#13009)
* SysTools * Parser * GHC.Builtin * GHC.Iface.Recomp * Settings Update Haddock submodule Metric Decrease: Naperian parsing001
Diffstat (limited to 'compiler/GHC/Iface')
-rw-r--r--compiler/GHC/Iface/Binary.hs6
-rw-r--r--compiler/GHC/Iface/Ext/Ast.hs2
-rw-r--r--compiler/GHC/Iface/Ext/Binary.hs4
-rw-r--r--compiler/GHC/Iface/Load.hs12
-rw-r--r--compiler/GHC/Iface/Recomp.hs4
-rw-r--r--compiler/GHC/Iface/Recomp/Binary.hs49
-rw-r--r--compiler/GHC/Iface/Recomp/Flags.hs184
-rw-r--r--compiler/GHC/Iface/Syntax.hs4
-rw-r--r--compiler/GHC/Iface/Type.hs13
9 files changed, 256 insertions, 22 deletions
diff --git a/compiler/GHC/Iface/Binary.hs b/compiler/GHC/Iface/Binary.hs
index 07a9da4c96..2e1953ade7 100644
--- a/compiler/GHC/Iface/Binary.hs
+++ b/compiler/GHC/Iface/Binary.hs
@@ -36,7 +36,7 @@ module GHC.Iface.Binary (
import GhcPrelude
import GHC.Tc.Utils.Monad
-import PrelInfo ( isKnownKeyName, lookupKnownKeyName )
+import GHC.Builtin.Utils ( isKnownKeyName, lookupKnownKeyName )
import GHC.Iface.Env
import GHC.Driver.Types
import GHC.Types.Module
@@ -54,7 +54,7 @@ import Outputable
import GHC.Types.Name.Cache
import GHC.Platform
import FastString
-import Constants
+import GHC.Settings.Constants
import Util
import Data.Array
@@ -355,7 +355,7 @@ serialiseName bh name _ = do
-- 10xxxxxx xxyyyyyy yyyyyyyy yyyyyyyy
-- A known-key name. x is the Unique's Char, y is the int part. We assume that
-- all known-key uniques fit in this space. This is asserted by
--- PrelInfo.knownKeyNamesOkay.
+-- GHC.Builtin.Utils.knownKeyNamesOkay.
--
-- During serialization we check for known-key things using isKnownKeyName.
-- During deserialization we use lookupKnownKeyName to get from the unique back
diff --git a/compiler/GHC/Iface/Ext/Ast.hs b/compiler/GHC/Iface/Ext/Ast.hs
index 41610d1625..c3b144dbfa 100644
--- a/compiler/GHC/Iface/Ext/Ast.hs
+++ b/compiler/GHC/Iface/Ext/Ast.hs
@@ -37,7 +37,7 @@ import GHC.Types.Name.Env ( NameEnv, emptyNameEnv, extendNameEnv, lookup
import GHC.Types.SrcLoc
import GHC.Tc.Utils.Zonk ( hsLitType, hsPatType )
import GHC.Core.Type ( mkVisFunTys, Type )
-import TysWiredIn ( mkListTy, mkSumTy )
+import GHC.Builtin.Types ( mkListTy, mkSumTy )
import GHC.Types.Var ( Id, Var, setVarName, varName, varType )
import GHC.Tc.Types
import GHC.Iface.Make ( mkIfaceExports )
diff --git a/compiler/GHC/Iface/Ext/Binary.hs b/compiler/GHC/Iface/Ext/Binary.hs
index 1a231b95f7..a90234c60f 100644
--- a/compiler/GHC/Iface/Ext/Binary.hs
+++ b/compiler/GHC/Iface/Ext/Binary.hs
@@ -15,7 +15,7 @@ module GHC.Iface.Ext.Binary
)
where
-import GHC.Settings ( maybeRead )
+import GHC.Settings.Utils ( maybeRead )
import Config ( cProjectVersion )
import GhcPrelude
@@ -27,7 +27,7 @@ import GHC.Types.Module ( Module )
import GHC.Types.Name
import GHC.Types.Name.Cache
import Outputable
-import PrelInfo
+import GHC.Builtin.Utils
import GHC.Types.SrcLoc as SrcLoc
import GHC.Types.Unique.Supply ( takeUniqFromSupply )
import GHC.Types.Unique
diff --git a/compiler/GHC/Iface/Load.hs b/compiler/GHC/Iface/Load.hs
index 2108e84079..8fc46734c2 100644
--- a/compiler/GHC/Iface/Load.hs
+++ b/compiler/GHC/Iface/Load.hs
@@ -49,12 +49,12 @@ import GHC.Types.Basic hiding (SuccessFlag(..))
import GHC.Tc.Utils.Monad
import Binary ( BinData(..) )
-import Constants
-import PrelNames
-import PrelInfo
-import PrimOp ( allThePrimOps, primOpFixity, primOpOcc )
-import GHC.Types.Id.Make ( seqId )
-import TysPrim ( funTyConName )
+import GHC.Settings.Constants
+import GHC.Builtin.Names
+import GHC.Builtin.Utils
+import GHC.Builtin.PrimOps ( allThePrimOps, primOpFixity, primOpOcc )
+import GHC.Types.Id.Make ( seqId )
+import GHC.Builtin.Types.Prim ( funTyConName )
import GHC.Core.Rules
import GHC.Core.TyCon
import GHC.Types.Annotations
diff --git a/compiler/GHC/Iface/Recomp.hs b/compiler/GHC/Iface/Recomp.hs
index 4ecf9666ee..57809a6d59 100644
--- a/compiler/GHC/Iface/Recomp.hs
+++ b/compiler/GHC/Iface/Recomp.hs
@@ -15,9 +15,9 @@ where
import GhcPrelude
import GHC.Iface.Syntax
-import BinFingerprint
+import GHC.Iface.Recomp.Binary
import GHC.Iface.Load
-import FlagChecker
+import GHC.Iface.Recomp.Flags
import GHC.Types.Annotations
import GHC.Core
diff --git a/compiler/GHC/Iface/Recomp/Binary.hs b/compiler/GHC/Iface/Recomp/Binary.hs
new file mode 100644
index 0000000000..55742b55eb
--- /dev/null
+++ b/compiler/GHC/Iface/Recomp/Binary.hs
@@ -0,0 +1,49 @@
+{-# LANGUAGE CPP #-}
+
+-- | Computing fingerprints of values serializeable with GHC's "Binary" module.
+module GHC.Iface.Recomp.Binary
+ ( -- * Computing fingerprints
+ fingerprintBinMem
+ , computeFingerprint
+ , putNameLiterally
+ ) where
+
+#include "HsVersions.h"
+
+import GhcPrelude
+
+import Fingerprint
+import Binary
+import GHC.Types.Name
+import PlainPanic
+import Util
+
+fingerprintBinMem :: BinHandle -> IO Fingerprint
+fingerprintBinMem bh = withBinBuffer bh f
+ where
+ f bs =
+ -- we need to take care that we force the result here
+ -- lest a reference to the ByteString may leak out of
+ -- withBinBuffer.
+ let fp = fingerprintByteString bs
+ in fp `seq` return fp
+
+computeFingerprint :: (Binary a)
+ => (BinHandle -> Name -> IO ())
+ -> a
+ -> IO Fingerprint
+computeFingerprint put_nonbinding_name a = do
+ bh <- fmap set_user_data $ openBinMem (3*1024) -- just less than a block
+ put_ bh a
+ fp <- fingerprintBinMem bh
+ return fp
+ where
+ set_user_data bh =
+ setUserData bh $ newWriteState put_nonbinding_name putNameLiterally putFS
+
+-- | Used when we want to fingerprint a structure without depending on the
+-- fingerprints of external Names that it refers to.
+putNameLiterally :: BinHandle -> Name -> IO ()
+putNameLiterally bh name = ASSERT( isExternalName name ) do
+ put_ bh $! nameModule name
+ put_ bh $! nameOccName name
diff --git a/compiler/GHC/Iface/Recomp/Flags.hs b/compiler/GHC/Iface/Recomp/Flags.hs
new file mode 100644
index 0000000000..ff5b23b709
--- /dev/null
+++ b/compiler/GHC/Iface/Recomp/Flags.hs
@@ -0,0 +1,184 @@
+{-# 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 GhcPrelude
+
+import Binary
+import GHC.Driver.Session
+import GHC.Driver.Types
+import GHC.Types.Module
+import GHC.Types.Name
+import Fingerprint
+import GHC.Iface.Recomp.Binary
+-- 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 dflags@DynFlags{..} this_mod nameio =
+ let mainis = if mainModIs == this_mod then Just mainFunIs else Nothing
+ -- see #5878
+ -- pkgopts = (thisPackage dflags, 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)
+
+ -- -I, -D and -U flags affect CPP
+ cpp = ( map normalise $ flattenIncludes includePaths
+ -- normalise: eliminate spurious differences due to "./foo" vs "foo"
+ , picPOpts dflags
+ , opt_P_signature dflags)
+ -- See Note [Repeated -optP hashing]
+
+ -- Note [path flags and recompilation]
+ paths = [ hcSuf ]
+
+ -- -fprof-auto etc.
+ prof = if gopt Opt_SccProfilingOn dflags then fromEnum profAuto else 0
+
+ -- Ticky
+ ticky =
+ map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk]
+
+ flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel))
+
+ 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 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.
+-}
diff --git a/compiler/GHC/Iface/Syntax.hs b/compiler/GHC/Iface/Syntax.hs
index 131db67141..3c707bc348 100644
--- a/compiler/GHC/Iface/Syntax.hs
+++ b/compiler/GHC/Iface/Syntax.hs
@@ -45,7 +45,7 @@ module GHC.Iface.Syntax (
import GhcPrelude
import GHC.Iface.Type
-import BinFingerprint
+import GHC.Iface.Recomp.Binary
import GHC.Core( IsOrphan, isOrphan )
import GHC.Types.Demand
import GHC.Types.Cpr
@@ -70,7 +70,7 @@ import GHC.Core.TyCon ( Role (..), Injectivity(..), tyConBndrVisArgFlag )
import Util( dropList, filterByList, notNull, unzipWith, debugIsOn )
import GHC.Core.DataCon (SrcStrictness(..), SrcUnpackedness(..))
import GHC.Utils.Lexeme (isLexSym)
-import TysWiredIn ( constraintKindTyConName )
+import GHC.Builtin.Types ( constraintKindTyConName )
import Util (seqList)
import Control.Monad
diff --git a/compiler/GHC/Iface/Type.hs b/compiler/GHC/Iface/Type.hs
index 85b1a19f40..6aedf0fd4c 100644
--- a/compiler/GHC/Iface/Type.hs
+++ b/compiler/GHC/Iface/Type.hs
@@ -62,14 +62,15 @@ module GHC.Iface.Type (
import GhcPrelude
-import {-# SOURCE #-} TysWiredIn ( coercibleTyCon, heqTyCon
+import {-# SOURCE #-} GHC.Builtin.Types
+ ( coercibleTyCon, heqTyCon
, liftedRepDataConTyCon, tupleTyConName )
import {-# SOURCE #-} GHC.Core.Type ( isRuntimeRepTy )
import GHC.Core.TyCon hiding ( pprPromotionQuote )
import GHC.Core.Coercion.Axiom
import GHC.Types.Var
-import PrelNames
+import GHC.Builtin.Names
import GHC.Types.Name
import GHC.Types.Basic
import Binary
@@ -267,7 +268,7 @@ We do the same for covars, naturally.
Note [Equality predicates in IfaceType]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
GHC has several varieties of type equality (see Note [The equality types story]
-in TysPrim for details). In an effort to avoid confusing users, we suppress
+in GHC.Builtin.Types.Prim for details). In an effort to avoid confusing users, we suppress
the differences during pretty printing unless certain flags are enabled.
Here is how each equality predicate* is printed in homogeneous and
heterogeneous contexts, depending on which combination of the
@@ -318,7 +319,7 @@ possible since we can't see through type synonyms. Consequently, we need to
record whether this particular application is homogeneous in IfaceTyConSort
for the purposes of pretty-printing.
-See Note [The equality types story] in TysPrim.
+See Note [The equality types story] in GHC.Builtin.Types.Prim.
-}
data IfaceTyConInfo -- Used to guide pretty-printing
@@ -343,7 +344,7 @@ data IfaceCoercion
| IfaceAxiomRuleCo IfLclName [IfaceCoercion]
-- There are only a fixed number of CoAxiomRules, so it suffices
-- to use an IfaceLclName to distinguish them.
- -- See Note [Adding built-in type families] in TcTypeNats
+ -- See Note [Adding built-in type families] in GHC.Builtin.Types.Literals
| IfaceUnivCo IfaceUnivCoProv Role IfaceType IfaceType
| IfaceSymCo IfaceCoercion
| IfaceTransCo IfaceCoercion IfaceCoercion
@@ -1345,7 +1346,7 @@ ppr_kind_type ctxt_prec = sdocOption sdocStarIsType $ \case
-- heqTyCon (~~)
--
-- See Note [Equality predicates in IfaceType]
--- and Note [The equality types story] in TysPrim
+-- and Note [The equality types story] in GHC.Builtin.Types.Prim
ppr_equality :: PprPrec -> IfaceTyCon -> [IfaceType] -> Maybe SDoc
ppr_equality ctxt_prec tc args
| hetero_eq_tc