[Git][ghc/ghc][wip/fendor/ghc-iface-sharing-avoid-reserialisation] Make sure to always invalidate correctly
Hannes Siebenhandl (@fendor)
gitlab at gitlab.haskell.org
Fri May 3 09:15:06 UTC 2024
Hannes Siebenhandl pushed to branch wip/fendor/ghc-iface-sharing-avoid-reserialisation at Glasgow Haskell Compiler / GHC
Commits:
4bcd2b69 by Fendor at 2024-05-03T11:14:49+02:00
Make sure to always invalidate correctly
Bump haddock submodule
- - - - -
9 changed files:
- compiler/GHC.hs
- compiler/GHC/Iface/Binary.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Tc/Errors/Hole.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Unit/Module/ModIface.hs
- utils/haddock
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -98,7 +98,32 @@ module GHC (
lookupGlobalName,
findGlobalAnns,
mkNamePprCtxForModule,
- ModIface, ModIface_(..),
+ ModIface,
+ mi_module,
+ mi_sig_of,
+ mi_hsc_src,
+ mi_src_hash,
+ mi_hi_bytes,
+ mi_deps,
+ mi_usages,
+ mi_exports,
+ mi_used_th,
+ mi_fixities,
+ mi_warns,
+ mi_anns,
+ mi_insts,
+ mi_fam_insts,
+ mi_rules,
+ mi_decls,
+ mi_extra_decls,
+ mi_globals,
+ mi_hpc,
+ mi_trust,
+ mi_trust_pkg,
+ mi_complete_matches,
+ mi_docs,
+ mi_final_exts,
+ mi_ext_fields,
SafeHaskellMode(..),
-- * Printing
=====================================
compiler/GHC/Iface/Binary.hs
=====================================
@@ -64,6 +64,7 @@ import Data.Word
import System.IO.Unsafe
import Data.Typeable (Typeable)
import qualified GHC.Data.Strict as Strict
+import Data.Function ((&))
-- ---------------------------------------------------------------------------
@@ -161,9 +162,9 @@ readBinIface profile name_cache checkHiWay traceBinIface hi_path = do
mod_iface <- getIfaceWithExtFields name_cache bh
- return mod_iface
- { mi_src_hash = src_hash
- }
+ return $ mod_iface
+ & addSourceFingerprint src_hash
+
getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface
getIfaceWithExtFields name_cache bh = do
@@ -176,10 +177,9 @@ getIfaceWithExtFields name_cache bh = do
seekBinReaderRel bh extFields_p_rel
extFields <- get bh
modIfaceData <- freezeBinHandle2 bh start
- pure mod_iface
- { mi_ext_fields = extFields
- , mi_hi_bytes = FullIfaceBinHandle $ Strict.Just modIfaceData
- }
+ pure $ mod_iface
+ & set_mi_ext_fields extFields
+ & set_mi_hi_bytes (FullIfaceBinHandle $ Strict.Just modIfaceData)
-- | This performs a get action after reading the dictionary and symbol
=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -117,6 +117,7 @@ import System.FilePath
import System.Directory
import GHC.Driver.Env.KnotVars
import GHC.Iface.Errors.Types
+import Data.Function ((&))
{-
************************************************************************
@@ -515,14 +516,12 @@ loadInterface doc_str mod from
; new_eps_anns <- tcIfaceAnnotations (mi_anns iface)
; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface)
- ; let { final_iface = iface {
- mi_decls = panic "No mi_decls in PIT",
- mi_insts = panic "No mi_insts in PIT",
- mi_fam_insts = panic "No mi_fam_insts in PIT",
- mi_rules = panic "No mi_rules in PIT",
- mi_anns = panic "No mi_anns in PIT"
- }
- }
+ ; let final_iface = iface
+ & set_mi_decls (panic "No mi_decls in PIT")
+ & set_mi_insts (panic "No mi_insts in PIT")
+ & set_mi_fam_insts (panic "No mi_fam_insts in PIT")
+ & set_mi_rules (panic "No mi_rules in PIT")
+ & set_mi_anns (panic "No mi_anns in PIT")
; let bad_boot = mi_boot iface == IsBoot
&& isJust (lookupKnotVars (if_rec_types gbl_env) mod)
@@ -1017,13 +1016,13 @@ readIface dflags name_cache wanted_mod file_path = do
-- See Note [GHC.Prim] in primops.txt.pp.
ghcPrimIface :: ModIface
ghcPrimIface
- = empty_iface {
- mi_exports = ghcPrimExports,
- mi_decls = [],
- mi_fixities = fixities,
- mi_final_exts = (mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities },
- mi_docs = Just ghcPrimDeclDocs -- See Note [GHC.Prim Docs]
- }
+ = empty_iface
+ & set_mi_exports ghcPrimExports
+ & set_mi_decls []
+ & set_mi_fixities fixities
+ & set_mi_final_exts ((mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities })
+ & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs]
+
where
empty_iface = emptyFullModIface gHC_PRIM
=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -144,7 +144,7 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do
full_iface <-
{-# SCC "addFingerprints" #-}
- addFingerprints hsc_env partial_iface{ mi_decls = decls }
+ addFingerprints hsc_env (set_mi_decls decls partial_iface)
-- Debug printing
let unit_state = hsc_units hsc_env
@@ -177,10 +177,7 @@ shareIface nc compressionLevel mi = do
rbh <- shrinkBinBuffer bh
seekBinReader rbh start
res <- getIfaceWithExtFields nc rbh
- let resiface = res
- { mi_src_hash = mi_src_hash mi
- , mi_globals = mi_globals mi
- }
+ let resiface = restoreFromOldModIface mi res
forceModIface resiface
return resiface
=====================================
compiler/GHC/Iface/Rename.hs
=====================================
@@ -44,6 +44,7 @@ import GHC.Utils.Panic
import qualified Data.Traversable as T
import Data.IORef
+import Data.Function ((&))
tcRnMsgMaybe :: IO (Either (Messages TcRnMessage) a) -> TcM a
tcRnMsgMaybe do_this = do
@@ -108,13 +109,14 @@ rnModIface hsc_env insts nsubst iface =
deps <- rnDependencies (mi_deps iface)
-- TODO:
-- mi_rules
- return iface { mi_module = mod
- , mi_sig_of = sig_of
- , mi_insts = insts
- , mi_fam_insts = fams
- , mi_exports = exports
- , mi_decls = decls
- , mi_deps = deps }
+ return $ iface
+ & set_mi_module mod
+ & set_mi_sig_of sig_of
+ & set_mi_insts insts
+ & set_mi_fam_insts fams
+ & set_mi_exports exports
+ & set_mi_decls decls
+ & set_mi_deps deps
-- | Rename just the exports of a 'ModIface'. Useful when we're doing
-- shaping prior to signature merging.
=====================================
compiler/GHC/Tc/Errors/Hole.hs
=====================================
@@ -76,7 +76,7 @@ import GHC.Tc.Utils.Unify ( tcSubTypeSigma )
import GHC.HsToCore.Docs ( extractDocs )
import GHC.Hs.Doc
-import GHC.Unit.Module.ModIface ( ModIface_(..) )
+import GHC.Unit.Module.ModIface ( mi_docs )
import GHC.Iface.Load ( loadInterfaceForName )
import GHC.Builtin.Utils (knownKeyNames)
=====================================
compiler/GHC/Tc/Utils/Backpack.hs
=====================================
@@ -87,6 +87,7 @@ import Control.Monad
import Data.List (find)
import GHC.Iface.Errors.Types
+import Data.Function ((&))
checkHsigDeclM :: ModIface -> TyThing -> TyThing -> TcRn ()
checkHsigDeclM sig_iface sig_thing real_thing = do
@@ -369,8 +370,8 @@ tcRnMergeSignatures hsc_env hpm orig_tcg_env iface =
thinModIface :: [AvailInfo] -> ModIface -> ModIface
thinModIface avails iface =
- iface {
- mi_exports = avails,
+ iface
+ & set_mi_exports avails
-- mi_fixities = ...,
-- mi_warns = ...,
-- mi_anns = ...,
@@ -378,10 +379,9 @@ thinModIface avails iface =
-- perhaps there might be two IfaceTopBndr that are the same
-- OccName but different Name. Requires better understanding
-- of invariants here.
- mi_decls = exported_decls ++ non_exported_decls ++ dfun_decls
+ & set_mi_decls (exported_decls ++ non_exported_decls ++ dfun_decls)
-- mi_insts = ...,
-- mi_fam_insts = ...,
- }
where
decl_pred occs decl = nameOccName (ifName decl) `elemOccSet` occs
filter_decls occs = filter (decl_pred occs . snd) (mi_decls iface)
=====================================
compiler/GHC/Unit/Module/ModIface.hs
=====================================
@@ -8,6 +8,8 @@
module GHC.Unit.Module.ModIface
( ModIface
, ModIface_
+ , restoreFromOldModIface
+ , addSourceFingerprint
, mi_module
, mi_sig_of
, mi_hsc_src
@@ -210,60 +212,60 @@ data IfaceBinHandle (phase :: ModIfacePhase) where
-- strict and others are not.
data ModIface_ (phase :: ModIfacePhase)
= ModIface {
- mi_module :: !Module, -- ^ Name of the module we are for
- mi_sig_of :: !(Maybe Module), -- ^ Are we a sig of another mod?
+ mi_module_ :: !Module, -- ^ Name of the module we are for
+ mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod?
- mi_hsc_src :: !HscSource, -- ^ Boot? Signature?
+ mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature?
- mi_deps :: Dependencies,
+ mi_deps_ :: Dependencies,
-- ^ The dependencies of the module. This is
-- consulted for directly-imported modules, but not
-- for anything else (hence lazy)
- mi_usages :: [Usage],
+ mi_usages_ :: [Usage],
-- ^ Usages; kept sorted so that it's easy to decide
-- whether to write a new iface file (changing usages
-- doesn't affect the hash of this module)
-- NOT STRICT! we read this field lazily from the interface file
-- It is *only* consulted by the recompilation checker
- mi_exports :: ![IfaceExport],
+ mi_exports_ :: ![IfaceExport],
-- ^ Exports
-- Kept sorted by (mod,occ), to make version comparisons easier
-- Records the modules that are the declaration points for things
-- exported by this module, and the 'OccName's of those things
- mi_used_th :: !Bool,
+ mi_used_th_ :: !Bool,
-- ^ Module required TH splices when it was compiled.
-- This disables recompilation avoidance (see #481).
- mi_fixities :: [(OccName,Fixity)],
+ mi_fixities_ :: [(OccName,Fixity)],
-- ^ Fixities
-- NOT STRICT! we read this field lazily from the interface file
- mi_warns :: IfaceWarnings,
+ mi_warns_ :: IfaceWarnings,
-- ^ Warnings
-- NOT STRICT! we read this field lazily from the interface file
- mi_anns :: [IfaceAnnotation],
+ mi_anns_ :: [IfaceAnnotation],
-- ^ Annotations
-- NOT STRICT! we read this field lazily from the interface file
- mi_decls :: [IfaceDeclExts phase],
+ mi_decls_ :: [IfaceDeclExts phase],
-- ^ Type, class and variable declarations
-- The hash of an Id changes if its fixity or deprecations change
-- (as well as its type of course)
-- Ditto data constructors, class operations, except that
-- the hash of the parent class/tycon changes
- mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo],
+ mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo],
-- ^ Extra variable definitions which are **NOT** exposed but when
-- combined with mi_decls allows us to restart code generation.
-- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs]
- mi_globals :: !(Maybe IfGlobalRdrEnv),
+ mi_globals_ :: !(Maybe IfGlobalRdrEnv),
-- ^ Binds all the things defined at the top level in
-- the /original source/ code for this module. which
-- is NOT the same as mi_exports, nor mi_decls (which
@@ -279,36 +281,36 @@ data ModIface_ (phase :: ModIfacePhase)
-- 'HomeModInfo', but that leads to more plumbing.
-- Instance declarations and rules
- mi_insts :: [IfaceClsInst], -- ^ Sorted class instance
- mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances
- mi_rules :: [IfaceRule], -- ^ Sorted rules
+ mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance
+ mi_fam_insts_ :: [IfaceFamInst], -- ^ Sorted family instances
+ mi_rules_ :: [IfaceRule], -- ^ Sorted rules
- mi_hpc :: !AnyHpcUsage,
+ mi_hpc_ :: !AnyHpcUsage,
-- ^ True if this program uses Hpc at any point in the program.
- mi_trust :: !IfaceTrustInfo,
+ mi_trust_ :: !IfaceTrustInfo,
-- ^ Safe Haskell Trust information for this module.
- mi_trust_pkg :: !Bool,
+ mi_trust_pkg_ :: !Bool,
-- ^ Do we require the package this module resides in be trusted
-- to trust this module? This is used for the situation where a
-- module is Safe (so doesn't require the package be trusted
-- itself) but imports some trustworthy modules from its own
-- package (which does require its own package be trusted).
-- See Note [Trust Own Package] in GHC.Rename.Names
- mi_complete_matches :: ![IfaceCompleteMatch],
+ mi_complete_matches_ :: ![IfaceCompleteMatch],
- mi_docs :: !(Maybe Docs),
+ mi_docs_ :: !(Maybe Docs),
-- ^ Docstrings and related data for use by haddock, the ghci
-- @:doc@ command, and other tools.
--
-- @Just _@ @<=>@ the module was built with @-haddock at .
- mi_final_exts :: !(IfaceBackendExts phase),
+ mi_final_exts_ :: !(IfaceBackendExts phase),
-- ^ Either `()` or `ModIfaceBackend` for
-- a fully instantiated interface.
- mi_ext_fields :: !ExtensibleFields,
+ mi_ext_fields_ :: !ExtensibleFields,
-- ^ Additional optional fields, where the Map key represents
-- the field name, resulting in a (size, serialized data) pair.
-- Because the data is intended to be serialized through the
@@ -317,9 +319,9 @@ data ModIface_ (phase :: ModIfacePhase)
-- chosen over `ByteString`s.
--
- mi_src_hash :: !Fingerprint,
+ mi_src_hash_ :: !Fingerprint,
-- ^ Hash of the .hs source, used for recompilation checking.
- mi_hi_bytes :: !(IfaceBinHandle phase)
+ mi_hi_bytes_ :: !(IfaceBinHandle phase)
}
{-
@@ -399,34 +401,34 @@ renameFreeHoles fhs insts =
-- See Note [Strictness in ModIface] about where we use lazyPut vs put
instance Binary ModIface where
put_ bh (ModIface {
- mi_module = mod,
- mi_sig_of = sig_of,
- mi_hsc_src = hsc_src,
- mi_src_hash = _src_hash, -- Don't `put_` this in the instance
+ mi_module_ = mod,
+ mi_sig_of_ = sig_of,
+ mi_hsc_src_ = hsc_src,
+ mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance
-- because we are going to write it
-- out separately in the actual file
- mi_hi_bytes = _hi_bytes, -- TODO: explain
- mi_deps = deps,
- mi_usages = usages,
- mi_exports = exports,
- mi_used_th = used_th,
- mi_fixities = fixities,
- mi_warns = warns,
- mi_anns = anns,
- mi_decls = decls,
- mi_extra_decls = extra_decls,
- mi_insts = insts,
- mi_fam_insts = fam_insts,
- mi_rules = rules,
- mi_hpc = hpc_info,
- mi_trust = trust,
- mi_trust_pkg = trust_pkg,
- mi_complete_matches = complete_matches,
- mi_docs = docs,
- mi_ext_fields = _ext_fields, -- Don't `put_` this in the instance so we
+ mi_hi_bytes_ = _hi_bytes, -- TODO: explain
+ mi_deps_ = deps,
+ mi_usages_ = usages,
+ mi_exports_ = exports,
+ mi_used_th_ = used_th,
+ mi_fixities_ = fixities,
+ mi_warns_ = warns,
+ mi_anns_ = anns,
+ mi_decls_ = decls,
+ mi_extra_decls_ = extra_decls,
+ mi_insts_ = insts,
+ mi_fam_insts_ = fam_insts,
+ mi_rules_ = rules,
+ mi_hpc_ = hpc_info,
+ mi_trust_ = trust,
+ mi_trust_pkg_ = trust_pkg,
+ mi_complete_matches_ = complete_matches,
+ mi_docs_ = docs,
+ mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we
-- can deal with it's pointer in the header
-- when we write the actual file
- mi_final_exts = ModIfaceBackend {
+ mi_final_exts_ = ModIfaceBackend {
mi_iface_hash = iface_hash,
mi_mod_hash = mod_hash,
mi_flag_hash = flag_hash,
@@ -501,34 +503,34 @@ instance Binary ModIface where
complete_matches <- get bh
docs <- lazyGetMaybe bh
return (ModIface {
- mi_module = mod,
- mi_sig_of = sig_of,
- mi_hsc_src = hsc_src,
- mi_src_hash = fingerprint0, -- placeholder because this is dealt
+ mi_module_ = mod,
+ mi_sig_of_ = sig_of,
+ mi_hsc_src_ = hsc_src,
+ mi_src_hash_ = fingerprint0, -- placeholder because this is dealt
-- with specially when the file is read
- mi_hi_bytes = FullIfaceBinHandle Strict.Nothing,
- mi_deps = deps,
- mi_usages = usages,
- mi_exports = exports,
- mi_used_th = used_th,
- mi_anns = anns,
- mi_fixities = fixities,
- mi_warns = warns,
- mi_decls = decls,
- mi_extra_decls = extra_decls,
- mi_globals = Nothing,
- mi_insts = insts,
- mi_fam_insts = fam_insts,
- mi_rules = rules,
- mi_hpc = hpc_info,
- mi_trust = trust,
- mi_trust_pkg = trust_pkg,
+ mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing,
+ mi_deps_ = deps,
+ mi_usages_ = usages,
+ mi_exports_ = exports,
+ mi_used_th_ = used_th,
+ mi_anns_ = anns,
+ mi_fixities_ = fixities,
+ mi_warns_ = warns,
+ mi_decls_ = decls,
+ mi_extra_decls_ = extra_decls,
+ mi_globals_ = Nothing,
+ mi_insts_ = insts,
+ mi_fam_insts_ = fam_insts,
+ mi_rules_ = rules,
+ mi_hpc_ = hpc_info,
+ mi_trust_ = trust,
+ mi_trust_pkg_ = trust_pkg,
-- And build the cached values
- mi_complete_matches = complete_matches,
- mi_docs = docs,
- mi_ext_fields = emptyExtensibleFields, -- placeholder because this is dealt
+ mi_complete_matches_ = complete_matches,
+ mi_docs_ = docs,
+ mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt
-- with specially when the file is read
- mi_final_exts = ModIfaceBackend {
+ mi_final_exts_ = ModIfaceBackend {
mi_iface_hash = iface_hash,
mi_mod_hash = mod_hash,
mi_flag_hash = flag_hash,
@@ -551,39 +553,39 @@ type IfaceExport = AvailInfo
emptyPartialModIface :: Module -> PartialModIface
emptyPartialModIface mod
- = ModIface { mi_module = mod,
- mi_sig_of = Nothing,
- mi_hsc_src = HsSrcFile,
- mi_src_hash = fingerprint0,
- mi_hi_bytes = PartialIfaceBinHandle,
- mi_deps = noDependencies,
- mi_usages = [],
- mi_exports = [],
- mi_used_th = False,
- mi_fixities = [],
- mi_warns = IfWarnSome [] [],
- mi_anns = [],
- mi_insts = [],
- mi_fam_insts = [],
- mi_rules = [],
- mi_decls = [],
- mi_extra_decls = Nothing,
- mi_globals = Nothing,
- mi_hpc = False,
- mi_trust = noIfaceTrustInfo,
- mi_trust_pkg = False,
- mi_complete_matches = [],
- mi_docs = Nothing,
- mi_final_exts = (),
- mi_ext_fields = emptyExtensibleFields
+ = ModIface { mi_module_ = mod,
+ mi_sig_of_ = Nothing,
+ mi_hsc_src_ = HsSrcFile,
+ mi_src_hash_ = fingerprint0,
+ mi_hi_bytes_ = PartialIfaceBinHandle,
+ mi_deps_ = noDependencies,
+ mi_usages_ = [],
+ mi_exports_ = [],
+ mi_used_th_ = False,
+ mi_fixities_ = [],
+ mi_warns_ = IfWarnSome [] [],
+ mi_anns_ = [],
+ mi_insts_ = [],
+ mi_fam_insts_ = [],
+ mi_rules_ = [],
+ mi_decls_ = [],
+ mi_extra_decls_ = Nothing,
+ mi_globals_ = Nothing,
+ mi_hpc_ = False,
+ mi_trust_ = noIfaceTrustInfo,
+ mi_trust_pkg_ = False,
+ mi_complete_matches_ = [],
+ mi_docs_ = Nothing,
+ mi_final_exts_ = (),
+ mi_ext_fields_ = emptyExtensibleFields
}
emptyFullModIface :: Module -> ModIface
emptyFullModIface mod =
(emptyPartialModIface mod)
- { mi_decls = []
- , mi_hi_bytes = FullIfaceBinHandle Strict.Nothing
- , mi_final_exts = ModIfaceBackend
+ { mi_decls_ = []
+ , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing
+ , mi_final_exts_ = ModIfaceBackend
{ mi_iface_hash = fingerprint0,
mi_mod_hash = fingerprint0,
mi_flag_hash = fingerprint0,
@@ -618,36 +620,36 @@ emptyIfaceHashCache _occ = Nothing
instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase))
, NFData (IfaceDeclExts (phase :: ModIfacePhase))
) => NFData (ModIface_ phase) where
- rnf (ModIface{ mi_module, mi_sig_of, mi_hsc_src, mi_deps, mi_usages
- , mi_exports, mi_used_th, mi_fixities, mi_warns, mi_anns
- , mi_decls, mi_extra_decls, mi_globals, mi_insts
- , mi_fam_insts, mi_rules, mi_hpc, mi_trust, mi_trust_pkg
- , mi_complete_matches, mi_docs, mi_final_exts
- , mi_ext_fields, mi_src_hash })
- = rnf mi_module
- `seq` rnf mi_sig_of
- `seq` mi_hsc_src
- `seq` mi_deps
- `seq` mi_usages
- `seq` mi_exports
- `seq` rnf mi_used_th
- `seq` mi_fixities
- `seq` rnf mi_warns
- `seq` rnf mi_anns
- `seq` rnf mi_decls
- `seq` rnf mi_extra_decls
- `seq` rnf mi_globals
- `seq` rnf mi_insts
- `seq` rnf mi_fam_insts
- `seq` rnf mi_rules
- `seq` rnf mi_hpc
- `seq` mi_trust
- `seq` rnf mi_trust_pkg
- `seq` rnf mi_complete_matches
- `seq` rnf mi_docs
- `seq` mi_final_exts
- `seq` mi_ext_fields
- `seq` rnf mi_src_hash
+ rnf (ModIface{ mi_module_, mi_sig_of_, mi_hsc_src_, mi_deps_, mi_usages_
+ , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_
+ , mi_decls_, mi_extra_decls_, mi_globals_, mi_insts_
+ , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_
+ , mi_complete_matches_, mi_docs_, mi_final_exts_
+ , mi_ext_fields_, mi_src_hash_ })
+ = rnf mi_module_
+ `seq` rnf mi_sig_of_
+ `seq` mi_hsc_src_
+ `seq` mi_deps_
+ `seq` mi_usages_
+ `seq` mi_exports_
+ `seq` rnf mi_used_th_
+ `seq` mi_fixities_
+ `seq` rnf mi_warns_
+ `seq` rnf mi_anns_
+ `seq` rnf mi_decls_
+ `seq` rnf mi_extra_decls_
+ `seq` rnf mi_globals_
+ `seq` rnf mi_insts_
+ `seq` rnf mi_fam_insts_
+ `seq` rnf mi_rules_
+ `seq` rnf mi_hpc_
+ `seq` mi_trust_
+ `seq` rnf mi_trust_pkg_
+ `seq` rnf mi_complete_matches_
+ `seq` rnf mi_docs_
+ `seq` mi_final_exts_
+ `seq` mi_ext_fields_
+ `seq` rnf mi_src_hash_
`seq` ()
instance NFData (ModIfaceBackend) where
@@ -694,90 +696,151 @@ completePartialModIface :: PartialModIface
-> IfaceBinHandle 'ModIfaceFinal
-> ModIface
completePartialModIface partial decls extra_decls final_exts hi_bytes = partial
- { mi_decls = decls
- , mi_extra_decls = extra_decls
- , mi_final_exts = final_exts
- , mi_hi_bytes = hi_bytes
+ { mi_decls_ = decls
+ , mi_extra_decls_ = extra_decls
+ , mi_final_exts_ = final_exts
+ , mi_hi_bytes_ = hi_bytes
+ }
+
+addSourceFingerprint :: Fingerprint -> ModIface_ 'ModIfaceFinal -> ModIface_ 'ModIfaceFinal
+addSourceFingerprint val iface = iface { mi_src_hash_ = val }
+
+restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase
+restoreFromOldModIface old new = new
+ { mi_globals_ = mi_globals_ old
+ , mi_hsc_src_ = mi_hsc_src_ old
+ , mi_src_hash_ = mi_src_hash_ old
}
set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase
-set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module = val }
+set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val }
set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase
-set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of = val }
+set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val }
set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase
-set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src = val }
+set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val }
set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase
-set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash = val }
+set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val }
set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase
-set_mi_hi_bytes val iface = iface { mi_hi_bytes = val }
+set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val }
set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase
-set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps = val }
+set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val }
set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase
-set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages = val }
+set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val }
set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase
-set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports = val }
+set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val }
set_mi_used_th :: Bool -> ModIface_ phase -> ModIface_ phase
-set_mi_used_th val iface = clear_mi_hi_bytes $ iface { mi_used_th = val }
+set_mi_used_th val iface = clear_mi_hi_bytes $ iface { mi_used_th_ = val }
set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase
-set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities = val }
+set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val }
set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase
-set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns = val }
+set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val }
set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase
-set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns = val }
+set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val }
set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase
-set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts = val }
+set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val }
set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase
-set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts = val }
+set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val }
set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase
-set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules = val }
+set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val }
set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase
-set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls = val }
+set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val }
set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase
-set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls = val }
+set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val }
set_mi_globals :: Maybe IfGlobalRdrEnv -> ModIface_ phase -> ModIface_ phase
-set_mi_globals val iface = clear_mi_hi_bytes $ iface { mi_globals = val }
+set_mi_globals val iface = clear_mi_hi_bytes $ iface { mi_globals_ = val }
set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase
-set_mi_hpc val iface = clear_mi_hi_bytes $ iface { mi_hpc = val }
+set_mi_hpc val iface = clear_mi_hi_bytes $ iface { mi_hpc_ = val }
set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase
-set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust = val }
+set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val }
set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase
-set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg = val }
+set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val }
set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase
-set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches = val }
+set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val }
set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase
-set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs = val }
+set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val }
set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase
-set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts = val }
+set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val }
set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase
-set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields = val }
+set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val }
clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes iface = iface
- { mi_hi_bytes = case mi_hi_bytes iface of
+ { mi_hi_bytes_ = case mi_hi_bytes iface of
PartialIfaceBinHandle -> PartialIfaceBinHandle
FullIfaceBinHandle _ -> FullIfaceBinHandle Strict.Nothing
}
+
+mi_module :: ModIface_ phase -> Module
+mi_module = mi_module_
+mi_sig_of :: ModIface_ phase -> Maybe Module
+mi_sig_of = mi_sig_of_
+mi_hsc_src :: ModIface_ phase -> HscSource
+mi_hsc_src = mi_hsc_src_
+mi_deps :: ModIface_ phase -> Dependencies
+mi_deps = mi_deps_
+mi_usages :: ModIface_ phase -> [Usage]
+mi_usages = mi_usages_
+mi_exports :: ModIface_ phase -> [IfaceExport]
+mi_exports = mi_exports_
+mi_used_th :: ModIface_ phase -> Bool
+mi_used_th = mi_used_th_
+mi_fixities :: ModIface_ phase -> [(OccName, Fixity)]
+mi_fixities = mi_fixities_
+mi_warns :: ModIface_ phase -> IfaceWarnings
+mi_warns = mi_warns_
+mi_anns :: ModIface_ phase -> [IfaceAnnotation]
+mi_anns = mi_anns_
+mi_decls :: ModIface_ phase -> [IfaceDeclExts phase]
+mi_decls = mi_decls_
+mi_extra_decls :: ModIface_ phase -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
+mi_extra_decls = mi_extra_decls_
+mi_globals :: ModIface_ phase -> Maybe IfGlobalRdrEnv
+mi_globals = mi_globals_
+mi_insts :: ModIface_ phase -> [IfaceClsInst]
+mi_insts = mi_insts_
+mi_fam_insts :: ModIface_ phase -> [IfaceFamInst]
+mi_fam_insts = mi_fam_insts_
+mi_rules :: ModIface_ phase -> [IfaceRule]
+mi_rules = mi_rules_
+mi_hpc :: ModIface_ phase -> AnyHpcUsage
+mi_hpc = mi_hpc_
+mi_trust :: ModIface_ phase -> IfaceTrustInfo
+mi_trust = mi_trust_
+mi_trust_pkg :: ModIface_ phase -> Bool
+mi_trust_pkg = mi_trust_pkg_
+mi_complete_matches :: ModIface_ phase -> [IfaceCompleteMatch]
+mi_complete_matches = mi_complete_matches_
+mi_docs :: ModIface_ phase -> Maybe Docs
+mi_docs = mi_docs_
+mi_final_exts :: ModIface_ phase -> IfaceBackendExts phase
+mi_final_exts = mi_final_exts_
+mi_ext_fields :: ModIface_ phase -> ExtensibleFields
+mi_ext_fields = mi_ext_fields_
+mi_src_hash :: ModIface_ phase -> Fingerprint
+mi_src_hash = mi_src_hash_
+mi_hi_bytes :: ModIface_ phase -> IfaceBinHandle phase
+mi_hi_bytes = mi_hi_bytes_
=====================================
utils/haddock
=====================================
@@ -1 +1 @@
-Subproject commit fa76e1ee98906f5bc8fc4598524610020b653412
+Subproject commit eaa6e1870997f09b9023cba09d6b5431cf5b0174
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4bcd2b69c92d8ea2cb465a0d3188a669abdfefde
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4bcd2b69c92d8ea2cb465a0d3188a669abdfefde
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240503/65f37df4/attachment-0001.html>
More information about the ghc-commits
mailing list