[Git][ghc/ghc][wip/romes/12935] Undo a bit more NonDet LblMap

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Tue Jul 9 09:47:20 UTC 2024



Rodrigo Mesquita pushed to branch wip/romes/12935 at Glasgow Haskell Compiler / GHC


Commits:
f526e1ae by Rodrigo Mesquita at 2024-07-09T10:47:09+01:00
Undo a bit more NonDet LblMap

- - - - -


2 changed files:

- compiler/GHC/Cmm/Dataflow/Label/NonDet.hs
- compiler/GHC/Cmm/Info/Build.hs


Changes:

=====================================
compiler/GHC/Cmm/Dataflow/Label/NonDet.hs
=====================================
@@ -73,7 +73,6 @@ module GHC.Cmm.Dataflow.Label.NonDet
     , nonDetMapFoldMapWithKey
     , nonDetMapKeys
     , nonDetMapToList
-    , fromDetMap
     ) where
 
 import GHC.Prelude
@@ -92,7 +91,6 @@ import qualified GHC.Data.Word64Map.Strict as M
 import Data.List (foldl1')
 
 import GHC.Cmm.Dataflow.Label (Label(..), mkHooplLabel)
-import qualified GHC.Cmm.Dataflow.Label as Det
 
 -----------------------------------------------------------------------------
 -- LabelSet
@@ -268,9 +266,6 @@ nonDetMapKeys (LM m) = map (mkHooplLabel . fst) (M.toList m)
 nonDetMapToList :: LabelMap b -> [(Label, b)]
 nonDetMapToList (LM m) = [(mkHooplLabel k, v) | (k, v) <- M.toList m]
 
-fromDetMap :: Det.LabelMap a -> LabelMap a
-fromDetMap = mapFromList . Det.mapToList
-
 -----------------------------------------------------------------------------
 -- Instances
 


=====================================
compiler/GHC/Cmm/Info/Build.hs
=====================================
@@ -27,7 +27,6 @@ import GHC.Cmm.Config
 import GHC.Cmm.Dataflow.Block
 import GHC.Cmm.Dataflow.Graph
 import GHC.Cmm.Dataflow.Label
-import qualified GHC.Cmm.Dataflow.Label.NonDet as NonDet
 import GHC.Cmm.Dataflow
 import GHC.Unit.Module
 import GHC.Data.Graph.Directed
@@ -537,7 +536,7 @@ newtype CAFfyLabel = CAFfyLabel CLabel
 deriving newtype instance OutputableP env CLabel => OutputableP env CAFfyLabel
 
 type CAFSet = Set CAFfyLabel
-type CAFEnv = NonDet.LabelMap CAFSet
+type CAFEnv = LabelMap CAFSet
 
 -- | Records the CAFfy references of a set of static data decls.
 type DataCAFEnv = Map CLabel CAFSet
@@ -603,10 +602,8 @@ cafAnal
   -> CmmGraph
   -> CAFEnv
 cafAnal platform contLbls topLbl cmmGraph =
-  -- ToDo: Is this worth it, or does it shadow the cost of deterministic mapUnion?
-  NonDet.fromDetMap $
-    analyzeCmmBwd cafLattice
-      (cafTransfers platform contLbls (g_entry cmmGraph) topLbl) cmmGraph mapEmpty
+  analyzeCmmBwd cafLattice
+    (cafTransfers platform contLbls (g_entry cmmGraph) topLbl) cmmGraph mapEmpty
 
 
 cafLattice :: DataflowLattice CAFSet
@@ -782,7 +779,7 @@ depAnalSRTs platform cafEnv cafEnv_static decls =
           | (l, lbl) <- labelledBlocks
           , Just (cafs :: Set CAFfyLabel) <-
               [case l of
-                 BlockLabel l -> NonDet.mapLookup l cafEnv
+                 BlockLabel l -> mapLookup l cafEnv
                  DeclLabel cl -> Map.lookup cl cafEnv_static]
           , let cafs' = Set.delete lbl cafs
           ]
@@ -817,7 +814,7 @@ getCAFs platform cafEnv = mapMaybe getCAFLabel
       | Just info <- mapLookup (g_entry g) (info_tbls top_info)
       , let rep = cit_rep info
       , isStaticRep rep && isThunkRep rep
-      , Just cafs <- NonDet.mapLookup (g_entry g) cafEnv
+      , Just cafs <- mapLookup (g_entry g) cafEnv
       = Just (Just (g_entry g), mkCAFfyLabel platform top_lbl, cafs)
 
       | otherwise
@@ -910,7 +907,7 @@ doSRTs cfg moduleSRTInfo dus procs data_ = do
                 CmmStaticsRaw lbl _ -> (lbl, set)
 
       (proc_envs, procss) = unzip procs
-      cafEnv = NonDet.mapUnions proc_envs
+      cafEnv = mapUnions proc_envs -- ToDo: May be more expensive now with LabelMap
       decls = map (cmmDataDeclCmmDecl . snd) data_ ++ concat procss
       staticFuns = mapFromList (getStaticFuns decls)
 



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

-- 
This project does not include diff previews in email notifications.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f526e1aee078712a5ae611d73fe90afa5e5095cb
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/20240709/7fff9529/attachment-0001.html>


More information about the ghc-commits mailing list