Skip to content
Snippets Groups Projects
Commit ed1ed5c6 authored by Rodrigo Mesquita's avatar Rodrigo Mesquita :seedling: Committed by Marge Bot
Browse files

Revert mapMG renaming

We had previously renamed this function for consistency, but that caused unnecessary breakage
parent 9e464ad0
No related branches found
No related tags found
No related merge requests found
Pipeline #104275 canceled
......@@ -74,7 +74,7 @@ module GHC (
compileToCoreModule, compileToCoreSimplified,
-- * Inspecting the module structure of the program
ModuleGraph, emptyMG, mgMap, mkModuleGraph, mgModSummaries,
ModuleGraph, emptyMG, mapMG, mkModuleGraph, mgModSummaries,
mgLookupModule,
ModSummary(..), ms_mod_name, ModLocation(..),
pattern ModLocation,
......@@ -874,7 +874,7 @@ setProgramDynFlags_ invalidate_needed dflags = do
--
invalidateModSummaryCache :: GhcMonad m => m ()
invalidateModSummaryCache =
modifySession $ \h -> h { hsc_mod_graph = mgMap inval (hsc_mod_graph h) }
modifySession $ \h -> h { hsc_mod_graph = mapMG inval (hsc_mod_graph h) }
where
inval ms = ms { ms_hs_hash = fingerprint0 }
......
......@@ -46,7 +46,7 @@ module GHC.Unit.Module.Graph
-- (without changing the 'ModuleGraph' structure itself!).
-- 'mgModSummaries' lists out all 'ModSummary's, and
-- 'mgLookupModule' looks up a 'ModSummary' for a given module.
, mgMap, mgMapM
, mapMG, mgMapM
, mgModSummaries
, mgLookupModule
......@@ -239,8 +239,8 @@ lengthMG = length . mg_mss
-- | Map a function 'f' over all the 'ModSummaries'.
-- To preserve invariants, 'f' can't change the isBoot status.
mgMap :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
mgMap f mg@ModuleGraph{..} = mg
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
mapMG f mg@ModuleGraph{..} = mg
{ mg_mss = flip fmap mg_mss $ \case
InstantiationNode uid iuid -> InstantiationNode uid iuid
LinkNode uid nks -> LinkNode uid nks
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment