[Git][ghc/ghc][wip/fendor/ghc-iface-sharing-avoid-reserialisation] Avoid unneccessarily re-serialising the `ModIface`

Hannes Siebenhandl (@fendor) gitlab at gitlab.haskell.org
Mon May 6 15:22:54 UTC 2024



Hannes Siebenhandl pushed to branch wip/fendor/ghc-iface-sharing-avoid-reserialisation at Glasgow Haskell Compiler / GHC


Commits:
fb7238c5 by Fendor at 2024-05-06T17:22:32+02:00
Avoid unneccessarily re-serialising the `ModIface`

To reduce memory usage of `ModIface`, we serialise `ModIface` to an
in-memory byte array, which implicitly shares duplicated values.

This serailised byte array can be reused to avoid work when we actually
write the `ModIface` to disk.
We introduce a new field to `ModIface` which allows us to save the byte
array, and write it to disk if the `ModIface` wasn't changed after the
initial serialisation.

This requires us to change absolute offsets, for example to jump to the
deduplication table for `Name` or `FastString` with relative offsets, as
the deduplication byte array doesn't contain header information, such as
fingerprints.
To allow us to dump the binary blob to disk, we need to replace all
absolute offsets with relative ones.

This leads to new primitives for `ModIface`, which help to construct
relative offsets.

- - - - -


15 changed files:

- compiler/GHC.hs
- compiler/GHC/Iface/Binary.hs
- compiler/GHC/Iface/Ext/Binary.hs
- compiler/GHC/Iface/Ext/Fields.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Tc/Errors/Hole.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Unit/Module/ModIface.hs
- compiler/GHC/Utils/Binary.hs
- testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.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
=====================================
@@ -63,6 +63,8 @@ import Data.Map.Strict (Map)
 import Data.Word
 import System.IO.Unsafe
 import Data.Typeable (Typeable)
+import qualified GHC.Data.Strict as Strict
+import Data.Function ((&))
 
 
 -- ---------------------------------------------------------------------------
@@ -160,21 +162,24 @@ 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
-  extFields_p <- get bh
+  start <- tellBinReader bh
+  extFields_p_rel <- getRelBin bh
 
   mod_iface <- getWithUserData name_cache bh
 
-  seekBinReader bh extFields_p
+  seekBinReader bh start
+  seekBinReaderRel bh extFields_p_rel
   extFields <- get bh
-  pure mod_iface
-    { mi_ext_fields = extFields
-    }
+  modIfaceData <- freezeBinHandle2 bh start
+  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
@@ -204,7 +209,7 @@ getTables name_cache bh = do
         -- add it to the 'ReaderUserData' of 'ReadBinHandle'.
         decodeReaderTable :: Typeable a => ReaderTable a -> ReadBinHandle -> IO ReadBinHandle
         decodeReaderTable tbl bh0 = do
-          table <- Binary.forwardGet bh (getTable tbl bh0)
+          table <- Binary.forwardGetRel bh (getTable tbl bh0)
           let binaryReader = mkReaderFromTable tbl table
           pure $ addReaderToUserData binaryReader bh0
 
@@ -241,11 +246,18 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do
     -- And send the result to the file
     writeBinMem bh hi_path
 
--- | Puts the 'ModIface'
+-- | Puts the 'ModIface' to the 'WriteBinHandle'.
+--
+-- This avoids serialisation of the 'ModIface' if the fields 'mi_hi_bytes' contains a
+-- 'Just' value. This fields can only be populated by reading the 'ModIface' using
+-- 'getIfaceWithExtFields' and not modifying it in any way afterwards.
 putIfaceWithExtFields :: TraceBinIFace -> CompressionIFace -> WriteBinHandle -> ModIface -> IO ()
 putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface =
-  forwardPut_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do
-    putWithUserData traceBinIface compressionLevel bh mod_iface
+  case mi_hi_bytes mod_iface of
+    FullIfaceBinHandle Strict.Nothing -> do
+      forwardPutRel_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do
+        putWithUserData traceBinIface compressionLevel bh mod_iface
+    FullIfaceBinHandle (Strict.Just binData) -> putFullBinData bh binData
 
 -- | Put a piece of data with an initialised `UserData` field. This
 -- is necessary if you want to serialise Names or FastStrings.
@@ -316,7 +328,7 @@ putAllTables _ [] act = do
   a <- act
   pure ([], a)
 putAllTables bh (x : xs) act = do
-  (r, (res, a)) <- forwardPut bh (const $ putTable x bh) $ do
+  (r, (res, a)) <- forwardPutRel bh (const $ putTable x bh) $ do
     putAllTables bh xs act
   pure (r : res, a)
 
@@ -468,7 +480,7 @@ to the table we need to deserialise first.
 What deduplication tables exist and the order of serialisation is currently statically specified
 in 'putWithTables'. 'putWithTables' also takes care of the serialisation of used deduplication tables.
 The deserialisation of the deduplication tables happens 'getTables', using 'Binary' utility
-functions such as 'forwardGet'.
+functions such as 'forwardGetRel'.
 
 Here, a visualisation of the table structure we currently have (ignoring 'ExtensibleFields'):
 
@@ -529,7 +541,6 @@ initWriteIfaceType compressionLevel = do
         putGenericSymTab sym_tab bh ty
       _ -> putIfaceType bh ty
 
-
     fullIfaceTypeSerialiser sym_tab bh ty = do
       put_ bh ifaceTypeSharedByte
       putGenericSymTab sym_tab bh ty


=====================================
compiler/GHC/Iface/Ext/Binary.hs
=====================================
@@ -235,7 +235,7 @@ readHieFileContents bh0 name_cache = do
   get bh1
   where
     get_dictionary tbl bin_handle = do
-      fsTable <- Binary.forwardGet bin_handle (getTable tbl bin_handle)
+      fsTable <- Binary.forwardGetRel bin_handle (getTable tbl bin_handle)
       let
         fsReader = mkReaderFromTable tbl fsTable
         bhFs = addReaderToUserData fsReader bin_handle


=====================================
compiler/GHC/Iface/Ext/Fields.hs
=====================================
@@ -41,7 +41,7 @@ instance Binary ExtensibleFields where
     -- to point to the start of each payload:
     forM_ header_entries $ \(field_p_p, dat) -> do
       field_p <- tellBinWriter bh
-      putAt bh field_p_p field_p
+      putAtRel bh field_p_p field_p
       seekBinWriter bh field_p
       put_ bh dat
 
@@ -50,11 +50,11 @@ instance Binary ExtensibleFields where
 
     -- Get the names and field pointers:
     header_entries <- replicateM n $
-      (,) <$> get bh <*> get bh
+      (,) <$> get bh <*> getRelBin bh
 
     -- Seek to and get each field's payload:
     fields <- forM header_entries $ \(name, field_p) -> do
-      seekBinReader bh field_p
+      seekBinReaderRel bh field_p
       dat <- get bh
       return (name, dat)
 


=====================================
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
 
@@ -1107,7 +1106,7 @@ pprModIfaceSimple unit_state iface =
 --
 -- The UnitState is used to pretty-print units
 pprModIface :: UnitState -> ModIface -> SDoc
-pprModIface unit_state iface at ModIface{ mi_final_exts = exts }
+pprModIface unit_state iface
  = vcat [ text "interface"
                 <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface)
                 <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty)
@@ -1148,6 +1147,7 @@ pprModIface unit_state iface at ModIface{ mi_final_exts = exts }
         , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface))
         ]
   where
+    exts = mi_final_exts iface
     pp_hsc_src HsBootFile = text "[boot]"
     pp_hsc_src HsigFile   = text "[hsig]"
     pp_hsc_src HsSrcFile  = Outputable.empty


=====================================
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
@@ -153,8 +153,24 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do
     final_iface <- shareIface (hsc_NC hsc_env) (flagsToIfCompression $ hsc_dflags hsc_env) full_iface
     return final_iface
 
+-- | Compress an 'ModIface' and share as many values as possible, depending on the 'CompressionIFace' level.
+-- See Note [Sharing of ModIface].
+--
+-- We compress the 'ModIface' by serialising the 'ModIface' to an in-memory byte array, and then deserialising it.
+-- The deserialisation will deduplicate certain values depending on the 'CompressionIFace' level.
+-- See Note [Deduplication during iface binary serialisation] for how we do that.
+--
+-- Additionally, we cache the serialised byte array, so if the 'ModIface' is not modified
+-- after calling 'shareIface', 'writeBinIface' will reuse that buffer without serialising the 'ModIface' again.
+-- Modifying the 'ModIface' forces us to re-serialise it again.
 shareIface :: NameCache -> CompressionIFace -> ModIface -> IO ModIface
-shareIface _ NormalCompression  mi = pure mi
+shareIface _ NormalCompression mi = do
+  -- In 'NormalCompression', the sharing isn't reducing the memory usage, as 'Name's and 'FastString's are
+  -- already shared, and at this compression level, we don't compress/share anything else.
+  -- Thus, for a brief moment we simply double the memory residency for no reason.
+  -- Therefore, we only try to share expensive values if the compression mode is higher than
+  -- 'NormalCompression'
+  pure mi
 shareIface nc compressionLevel  mi = do
   bh <- openBinMem (1024 * 1024)
   start <- tellBinWriter bh
@@ -162,10 +178,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
 
@@ -322,40 +335,40 @@ mkIface_ hsc_env
         icomplete_matches = map mkIfaceCompleteMatch complete_matches
         !rdrs = maybeGlobalRdrEnv rdr_env
 
-    ModIface {
-          mi_module      = this_mod,
+    emptyPartialModIface this_mod
           -- Need to record this because it depends on the -instantiated-with flag
           -- which could change
-          mi_sig_of      = if semantic_mod == this_mod
+          & set_mi_sig_of      ( if semantic_mod == this_mod
                             then Nothing
-                            else Just semantic_mod,
-          mi_hsc_src     = hsc_src,
-          mi_deps        = deps,
-          mi_usages      = usages,
-          mi_exports     = mkIfaceExports exports,
+                            else Just semantic_mod)
+          & set_mi_hsc_src     ( hsc_src)
+          & set_mi_deps        ( deps)
+          & set_mi_usages      ( usages)
+          & set_mi_exports     ( mkIfaceExports exports)
 
           -- Sort these lexicographically, so that
           -- the result is stable across compilations
-          mi_insts       = sortBy cmp_inst     iface_insts,
-          mi_fam_insts   = sortBy cmp_fam_inst iface_fam_insts,
-          mi_rules       = sortBy cmp_rule     iface_rules,
-
-          mi_fixities    = fixities,
-          mi_warns       = warns,
-          mi_anns        = annotations,
-          mi_globals     = rdrs,
-          mi_used_th     = used_th,
-          mi_decls       = decls,
-          mi_extra_decls = extra_decls,
-          mi_hpc         = isHpcUsed hpc_info,
-          mi_trust       = trust_info,
-          mi_trust_pkg   = pkg_trust_req,
-          mi_complete_matches = icomplete_matches,
-          mi_docs        = docs,
-          mi_final_exts  = (),
-          mi_ext_fields  = emptyExtensibleFields,
-          mi_src_hash = ms_hs_hash mod_summary
-          }
+          & set_mi_insts       ( sortBy cmp_inst     iface_insts)
+          & set_mi_fam_insts   ( sortBy cmp_fam_inst iface_fam_insts)
+          & set_mi_rules       ( sortBy cmp_rule     iface_rules)
+
+          & set_mi_fixities    ( fixities)
+          & set_mi_warns       ( warns)
+          & set_mi_anns        ( annotations)
+          & set_mi_globals     ( rdrs)
+          & set_mi_used_th     ( used_th)
+          & set_mi_decls       ( decls)
+          & set_mi_extra_decls ( extra_decls)
+          & set_mi_hpc         ( isHpcUsed hpc_info)
+          & set_mi_trust       ( trust_info)
+          & set_mi_trust_pkg   ( pkg_trust_req)
+          & set_mi_complete_matches ( icomplete_matches)
+          & set_mi_docs        ( docs)
+          & set_mi_final_exts  ( ())
+          & set_mi_ext_fields  ( emptyExtensibleFields)
+          & set_mi_src_hash ( ms_hs_hash mod_summary)
+          & set_mi_hi_bytes ( PartialIfaceBinHandle)
+
   where
      cmp_rule     = lexicalCompareFS `on` ifRuleName
      -- Compare these lexicographically by OccName, *not* by unique,
@@ -522,3 +535,22 @@ That is, in Y,
 In the result of mkIfaceExports, the names are grouped by defining module,
 so we may need to split up a single Avail into multiple ones.
 -}
+
+{-
+Note [Sharing of ModIface]
+~~~~~~~~~~~~~~~~~~~~~~~~~~
+A 'ModIface' contains many duplicated values such as 'Name', 'FastString' and 'IfaceType'.
+'Name's and 'FastString's are already deduplicated by default using the 'NameCache' and
+'FastStringTable' respectively.
+However, 'IfaceType' can be quite expensive in terms of memory usage.
+To improve the sharing of 'IfaceType', we introduced deduplication tables during
+serialisation of 'ModIface', see Note [Deduplication during iface binary serialisation].
+
+We can improve the sharing of 'ModIface' at run-time as well, by serialising the 'ModIface' to
+an in-memory buffer, and then deserialising it again.
+This implicitly shares duplicated values.
+
+To avoid re-serialising the 'ModIface' when writing it to disk, we save the serialised 'ModIface' buffer
+in 'mi_hi_bytes_' field of said 'ModIface'. This buffer is written to disk directly in 'putIfaceWithExtFields'.
+If we have to modify the 'ModIface' after 'shareIface' is called, the buffer needs to be discarded.
+-}


=====================================
compiler/GHC/Iface/Recomp.hs
=====================================
@@ -83,6 +83,7 @@ import Data.Ord
 import Data.Containers.ListUtils
 import Data.Bifunctor
 import GHC.Iface.Errors.Ppr
+import qualified GHC.Data.Strict as Strict
 
 {-
   -----------------------------------------------
@@ -1283,7 +1284,9 @@ addFingerprints hsc_env iface0
       , mi_fix_fn         = fix_fn
       , mi_hash_fn        = lookupOccEnv local_env
       }
-    final_iface = iface0 { mi_decls = sorted_decls, mi_extra_decls = sorted_extra_decls, mi_final_exts = final_iface_exts }
+    final_iface = completePartialModIface iface0
+        (sorted_decls) (sorted_extra_decls) (final_iface_exts)
+        (FullIfaceBinHandle Strict.Nothing)
    --
    return final_iface
 


=====================================
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/Gen/Splice.hs
=====================================
@@ -1562,7 +1562,8 @@ lookupDeclDoc nm = do
       -- Wasn't in the current module. Try searching other external ones!
       mIface <- getExternalModIface nm
       case mIface of
-        Just ModIface { mi_docs = Just Docs{docs_decls = dmap} } ->
+        Just iface
+          | Just Docs{docs_decls = dmap} <- mi_docs iface ->
           pure $ renderHsDocStrings . map hsDocString <$> lookupUniqMap dmap nm
         _ -> pure Nothing
 
@@ -1578,7 +1579,8 @@ lookupArgDoc i nm = do
     Nothing -> do
       mIface <- getExternalModIface nm
       case mIface of
-        Just ModIface { mi_docs = Just Docs{docs_args = amap} } ->
+        Just iface
+          | Just Docs{docs_args = amap} <- mi_docs iface->
           pure $ renderHsDocString . hsDocString <$> (lookupUniqMap amap nm >>= IntMap.lookup i)
         _ -> pure Nothing
 


=====================================
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
=====================================
@@ -7,7 +7,61 @@
 
 module GHC.Unit.Module.ModIface
    ( ModIface
-   , ModIface_ (..)
+   , ModIface_
+   , restoreFromOldModIface
+   , addSourceFingerprint
+   , 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
+   , set_mi_module
+   , set_mi_sig_of
+   , set_mi_hsc_src
+   , set_mi_src_hash
+   , set_mi_hi_bytes
+   , set_mi_deps
+   , set_mi_usages
+   , set_mi_exports
+   , set_mi_used_th
+   , set_mi_fixities
+   , set_mi_warns
+   , set_mi_anns
+   , set_mi_insts
+   , set_mi_fam_insts
+   , set_mi_rules
+   , set_mi_decls
+   , set_mi_extra_decls
+   , set_mi_globals
+   , set_mi_hpc
+   , set_mi_trust
+   , set_mi_trust_pkg
+   , set_mi_complete_matches
+   , set_mi_docs
+   , set_mi_final_exts
+   , set_mi_ext_fields
+   , completePartialModIface
+   , IfaceBinHandle(..)
    , PartialModIface
    , ModIfaceBackend (..)
    , IfaceDeclExts
@@ -58,6 +112,7 @@ import GHC.Utils.Binary
 
 import Control.DeepSeq
 import Control.Exception
+import qualified GHC.Data.Strict as Strict
 
 {- Note [Interface file stages]
    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -139,7 +194,9 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where
   IfaceBackendExts 'ModIfaceCore = ()
   IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend
 
-
+data IfaceBinHandle (phase :: ModIfacePhase) where
+  PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore
+  FullIfaceBinHandle :: Strict.Maybe FullBinData -> IfaceBinHandle 'ModIfaceFinal
 
 -- | A 'ModIface' plus a 'ModDetails' summarises everything we know
 -- about a compiled module.  The 'ModIface' is the stuff *before* linking,
@@ -155,60 +212,60 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase 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
@@ -224,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
@@ -262,8 +319,13 @@ 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)
+                -- ^ A serialised in-memory buffer of this 'ModIface'.
+                -- If this handle is given, we can avoid serialising the 'ModIface'
+                -- when writing this 'ModIface' to disk, and write this buffer to disk instead.
+                -- See Note [Sharing of ModIface].
      }
 
 {-
@@ -343,33 +405,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_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,
@@ -444,33 +507,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_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,
@@ -487,42 +551,45 @@ instance Binary ModIface where
                    mi_hash_fn = mkIfaceHashCache decls
                  }})
 
+
 -- | The original names declared of a certain module that are exported
 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_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_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,
@@ -557,36 +624,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
@@ -626,5 +693,158 @@ type WhetherHasOrphans   = Bool
 -- | Does this module define family instances?
 type WhetherHasFamInst = Bool
 
+completePartialModIface :: PartialModIface
+  -> [(Fingerprint, IfaceDecl)]
+  -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
+  -> ModIfaceBackend
+  -> 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
+  }
+
+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_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_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase
+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_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase
+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_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase
+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_used_th :: Bool -> ModIface_ phase -> ModIface_ phase
+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_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase
+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_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase
+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_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase
+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_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_globals :: Maybe IfGlobalRdrEnv -> ModIface_ phase -> ModIface_ phase
+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_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase
+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_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase
+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_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_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase
+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
+      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_


=====================================
compiler/GHC/Utils/Binary.hs
=====================================
@@ -19,7 +19,7 @@
 --     http://www.cs.york.ac.uk/fp/nhc98/
 
 module GHC.Utils.Binary
-  ( {-type-}  Bin,
+  ( {-type-}  Bin, RelBin(..), getRelBin,
     {-class-} Binary(..),
     {-type-}  ReadBinHandle, WriteBinHandle,
     SymbolTable, Dictionary,
@@ -32,6 +32,7 @@ module GHC.Utils.Binary
 
    seekBinWriter,
    seekBinReader,
+   seekBinReaderRel,
    tellBinReader,
    tellBinWriter,
    castBin,
@@ -47,7 +48,9 @@ module GHC.Utils.Binary
    readBinMemN,
 
    putAt, getAt,
+   putAtRel,
    forwardPut, forwardPut_, forwardGet,
+   forwardPutRel, forwardPutRel_, forwardGetRel,
 
    -- * For writing instances
    putByte,
@@ -102,6 +105,9 @@ module GHC.Utils.Binary
    BindingName(..),
    simpleBindingNameWriter,
    simpleBindingNameReader,
+   FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData,
+   freezeBinHandle2,
+   BinArray,
   ) where
 
 import GHC.Prelude
@@ -156,7 +162,6 @@ import GHC.ForeignPtr           ( unsafeWithForeignPtr )
 import Unsafe.Coerce (unsafeCoerce)
 
 import GHC.Data.TrieMap
-
 type BinArray = ForeignPtr Word8
 
 #if !MIN_VERSION_base(4,15,0)
@@ -196,6 +201,51 @@ dataHandle (BinData size bin) = do
 handleData :: WriteBinHandle -> IO BinData
 handleData (WriteBinMem _ ixr _ binr) = BinData <$> readFastMutInt ixr <*> readIORef binr
 
+---------------------------------------------------------------
+-- FullBinData
+---------------------------------------------------------------
+
+data FullBinData = FullBinData
+  { fbd_readerUserData :: ReaderUserData
+  , fbd_off_s :: {-# UNPACK #-} !Int
+  -- ^ start offset
+  , fbd_off_e :: {-# UNPACK #-} !Int
+  -- ^ end offset
+  , fbd_size :: {-# UNPACK #-} !Int
+  -- ^ total buffer size
+  , fbd_buffer :: {-# UNPACK #-} !BinArray
+  }
+
+-- Equality and Ord assume that two distinct buffers are different, even if they compare the same things.
+instance Eq FullBinData where
+  (FullBinData _ b c d e) == (FullBinData _ b1 c1 d1 e1) = b == b1 && c == c1 && d == d1 && e == e1
+
+instance Ord FullBinData where
+  compare (FullBinData _ b c d e) (FullBinData _ b1 c1 d1 e1) =
+    compare b b1 `mappend` compare c c1 `mappend` compare d d1 `mappend` compare e e1
+
+putFullBinData :: WriteBinHandle -> FullBinData -> IO ()
+putFullBinData bh (FullBinData _ o1 o2 _sz ba) = do
+  let sz = o2 - o1
+  putPrim bh sz $ \dest ->
+    unsafeWithForeignPtr (ba `plusForeignPtr` o1) $ \orig ->
+    copyBytes dest orig sz
+
+freezeBinHandle :: Bin () -> ReadBinHandle -> IO FullBinData
+freezeBinHandle (BinPtr len) (ReadBinMem user_data ixr sz binr) = do
+  ix <- readFastMutInt ixr
+  pure (FullBinData user_data ix len sz binr)
+
+freezeBinHandle2 :: ReadBinHandle -> Bin () -> IO FullBinData
+freezeBinHandle2 (ReadBinMem user_data ixr sz binr) (BinPtr start) = do
+  ix <- readFastMutInt ixr
+  pure (FullBinData user_data start ix sz binr)
+
+thawBinHandle :: FullBinData -> IO ReadBinHandle
+thawBinHandle (FullBinData user_data ix _end sz ba) = do
+  ixr <- newFastMutInt ix
+  return $ ReadBinMem user_data ixr sz ba
+
 ---------------------------------------------------------------
 -- BinHandle
 ---------------------------------------------------------------
@@ -289,9 +339,30 @@ unsafeUnpackBinBuffer (BS.BS arr len) = do
 newtype Bin a = BinPtr Int
   deriving (Eq, Ord, Show, Bounded)
 
+data RelBin a = RelBin !(Bin a) !(Bin a)
+  deriving (Eq, Ord, Show, Bounded)
+
+newtype RelBinPtr a = RelBinPtr (Bin a)
+
 castBin :: Bin a -> Bin b
 castBin (BinPtr i) = BinPtr i
 
+getRelBin :: ReadBinHandle -> IO (RelBin a)
+getRelBin bh = do
+  start <- tellBinReader bh
+  off <- get bh
+  pure $ RelBin start off
+
+makeAbsoluteBin ::  RelBin a -> Bin a
+makeAbsoluteBin (RelBin (BinPtr !start) (BinPtr !offset)) = BinPtr (start + offset)
+
+makeRelativeBin :: RelBin a -> RelBinPtr a
+makeRelativeBin (RelBin _ offset) = RelBinPtr offset
+
+toRelBin :: Bin (RelBinPtr a) -> Bin a -> RelBin a
+toRelBin (BinPtr !start) (BinPtr !goal) =
+  RelBin (BinPtr start) (BinPtr $! goal - start)
+
 ---------------------------------------------------------------
 -- class Binary
 ---------------------------------------------------------------
@@ -312,6 +383,9 @@ class Binary a where
 putAt  :: Binary a => WriteBinHandle -> Bin a -> a -> IO ()
 putAt bh p x = do seekBinWriter bh p; put_ bh x; return ()
 
+putAtRel :: WriteBinHandle -> Bin (RelBinPtr a) -> Bin a -> IO ()
+putAtRel bh from to = putAt bh from (makeRelativeBin $ toRelBin from to)
+
 getAt  :: Binary a => ReadBinHandle -> Bin a -> IO a
 getAt bh p = do seekBinReader bh p; get bh
 
@@ -393,12 +467,18 @@ seekBinNoExpandWriter (WriteBinMem _ ix_r sz_r _) (BinPtr !p) = do
         else writeFastMutInt ix_r p
 
 -- | SeekBin but without calling expandBin
-seekBinReader :: ReadBinHandle -> Bin a -> IO ()
+seekBinReader :: HasCallStack => ReadBinHandle -> Bin a -> IO ()
 seekBinReader (ReadBinMem _ ix_r sz_r _) (BinPtr !p) = do
   if (p > sz_r)
         then panic "seekBinReader: seek out of range"
         else writeFastMutInt ix_r p
 
+seekBinReaderRel :: HasCallStack => ReadBinHandle -> RelBin a -> IO ()
+seekBinReaderRel (ReadBinMem _ ix_r sz_r _) (RelBin (BinPtr !start) (BinPtr !offset)) = do
+  if (start + offset > sz_r)
+        then panic "seekBinReaderRel: seek out of range"
+        else writeFastMutInt ix_r (start + offset)
+
 writeBinMem :: WriteBinHandle -> FilePath -> IO ()
 writeBinMem (WriteBinMem _ ix_r _ arr_r) fn = do
   h <- openBinaryFile fn WriteMode
@@ -1119,6 +1199,11 @@ instance Binary (Bin a) where
   put_ bh (BinPtr i) = putWord32 bh (fromIntegral i :: Word32)
   get bh = do i <- getWord32 bh; return (BinPtr (fromIntegral (i :: Word32)))
 
+-- Instance uses fixed-width encoding to allow inserting
+-- Bin placeholders in the stream.
+instance Binary (RelBinPtr a) where
+  put_ bh (RelBinPtr i) = put_ bh i
+  get bh = RelBinPtr <$> get bh
 
 -- -----------------------------------------------------------------------------
 -- Forward reading/writing
@@ -1147,7 +1232,7 @@ forwardPut_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO ()
 forwardPut_ bh put_A put_B = void $ forwardPut bh put_A put_B
 
 -- | Read a value stored using a forward reference
-forwardGet :: ReadBinHandle -> IO a -> IO a
+forwardGet :: HasCallStack => ReadBinHandle -> IO a -> IO a
 forwardGet bh get_A = do
     -- read forward reference
     p <- get bh -- a BinPtr
@@ -1159,6 +1244,43 @@ forwardGet bh get_A = do
     seekBinReader bh p_a
     pure r
 
+
+-- | "forwardPutRel put_A put_B" outputs A after B but allows A to be read before B
+-- by using a forward reference.
+forwardPutRel :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b)
+forwardPutRel bh put_A put_B = do
+  -- write placeholder pointer to A
+  pre_a <- tellBinWriter bh
+  put_ bh pre_a
+
+  -- write B
+  r_b <- put_B
+
+  -- update A's pointer
+  a <- tellBinWriter bh
+  putAtRel bh pre_a a
+  seekBinNoExpandWriter bh a
+
+  -- write A
+  r_a <- put_A r_b
+  pure (r_a,r_b)
+
+forwardPutRel_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO ()
+forwardPutRel_ bh put_A put_B = void $ forwardPutRel bh put_A put_B
+
+-- | Read a value stored using a forward reference
+forwardGetRel :: ReadBinHandle -> IO a -> IO a
+forwardGetRel bh get_A = do
+    -- read forward reference
+    p <- getRelBin bh
+    -- store current position
+    p_a <- tellBinReader bh
+    -- go read the forward value, then seek back
+    seekBinReader bh $ makeAbsoluteBin p
+    r <- get_A
+    seekBinReader bh p_a
+    pure r
+
 -- -----------------------------------------------------------------------------
 -- Lazy reading/writing
 
@@ -1168,19 +1290,19 @@ lazyPut = lazyPut' put_
 lazyGet :: Binary a => ReadBinHandle -> IO a
 lazyGet = lazyGet' get
 
-lazyPut' :: HasDebugCallStack => (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO ()
+lazyPut' :: (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO ()
 lazyPut' f bh a = do
     -- output the obj with a ptr to skip over it:
     pre_a <- tellBinWriter bh
     put_ bh pre_a       -- save a slot for the ptr
     f bh a           -- dump the object
     q <- tellBinWriter bh     -- q = ptr to after object
-    putAt bh pre_a q    -- fill in slot before a with ptr to q
+    putAtRel bh pre_a q    -- fill in slot before a with ptr to q
     seekBinWriter bh q        -- finally carry on writing at q
 
 lazyGet' :: HasDebugCallStack => (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a
 lazyGet' f bh = do
-    p <- get bh -- a BinPtr
+    p <- getRelBin bh -- a BinPtr
     p_a <- tellBinReader bh
     a <- unsafeInterleaveIO $ do
         -- NB: Use a fresh rbm_off_r variable in the child thread, for thread
@@ -1189,7 +1311,7 @@ lazyGet' f bh = do
         let bh' = bh { rbm_off_r = off_r }
         seekBinReader bh' p_a
         f bh'
-    seekBinReader bh p -- skip over the object for now
+    seekBinReader bh (makeAbsoluteBin p) -- skip over the object for now
     return a
 
 -- | Serialize the constructor strictly but lazily serialize a value inside a
@@ -1483,13 +1605,13 @@ putGenericSymbolTable gen_sym_tab serialiser bh = do
                 mapM_ (\n -> serialiser bh n) (reverse todo)
                 loop
       snd <$>
-        (forwardPut bh (const $ readFastMutInt symtab_next >>= put_ bh) $
+        (forwardPutRel bh (const $ readFastMutInt symtab_next >>= put_ bh) $
           loop)
 
 -- | Read the elements of a 'GenericSymbolTable' from disk into a 'SymbolTable'.
 getGenericSymbolTable :: forall a . (ReadBinHandle -> IO a) -> ReadBinHandle -> IO (SymbolTable a)
 getGenericSymbolTable deserialiser bh = do
-  sz <- forwardGet bh (get bh) :: IO Int
+  sz <- forwardGetRel bh (get bh) :: IO Int
   mut_arr <- newArray_ (0, sz-1) :: IO (IOArray Int a)
   forM_ [0..(sz-1)] $ \i -> do
     f <- deserialiser bh


=====================================
testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs
=====================================
@@ -64,9 +64,10 @@ metaPlugin' _ meta = pprPanic "meta" (showAstData BlankSrcSpan BlankEpAnnotation
 
 interfaceLoadPlugin' :: [CommandLineOption] -> ModIface -> IfM lcl ModIface
 interfaceLoadPlugin' [name, "interface"] iface
-  = return $ iface { mi_exports = filter (availNotNamedAs name)
-                                         (mi_exports iface)
-                   }
+  = return $ set_mi_exports (filter (availNotNamedAs name)
+                                    (mi_exports iface))
+                            iface
+
 interfaceLoadPlugin' _ iface = return iface
 
 availNotNamedAs :: String -> AvailInfo -> Bool


=====================================
utils/haddock
=====================================
@@ -1 +1 @@
-Subproject commit fa76e1ee98906f5bc8fc4598524610020b653412
+Subproject commit eaa6e1870997f09b9023cba09d6b5431cf5b0174



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fb7238c50a4fb7b46db430b78794b4e0549c5f42

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fb7238c50a4fb7b46db430b78794b4e0549c5f42
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/20240506/089d97aa/attachment-0001.html>


More information about the ghc-commits mailing list