[Git][ghc/ghc][wip/romes/12935] 2 commits: StableNmCmp is invalid for internal names... also, rename all Id uniques

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Wed Jun 26 11:39:55 UTC 2024



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


Commits:
aae7e7b9 by Rodrigo Mesquita at 2024-06-26T12:37:20+01:00
StableNmCmp is invalid for internal names... also, rename all Id uniques

This fixes a really awful bug.

- - - - -
d910fe19 by Rodrigo Mesquita at 2024-06-26T12:39:40+01:00
Tweaks

- - - - -


3 changed files:

- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Cmm/UniqueRenamer.hs


Changes:

=====================================
compiler/GHC/Cmm/CLabel.hs
=====================================
@@ -343,8 +343,8 @@ newtype NeedExternDecl
 -- code-generation. See Note [Unique Determinism and code generation]
 instance Ord CLabel where
   compare (IdLabel a1 b1 c1) (IdLabel a2 b2 c2) =
-    -- Note [...TODO]: Use stable name comparison to guarantee non-determinism of uniques doesn't influence the order of IdLabels in eg data sections or symbol table.
-    stableNameCmp a1 a2 S.<>
+    -- Comparing names here should deterministic because all unique should have been renamed deterministically ......
+    compare a1 a2 S.<>
     compare b1 b2 S.<>
     compare c1 c2
   compare (CmmLabel a1 b1 c1 d1) (CmmLabel a2 b2 c2 d2) =
@@ -1852,13 +1852,10 @@ returns True.
 -- Note that not all Uniques are mapped over. Only those that can be safely alpha
 -- renamed, eg uniques of local symbols or of system names.
 -- See Note [....TODO]
+-- ROMES:TODO: We can do less work here, like, do we really need to rename AsmTempLabel, SRTLabel, LocalBlockLabel?
 mapInternalNonDetUniques :: Applicative m => (Unique -> m Unique) -> CLabel -> m CLabel
 mapInternalNonDetUniques f = \case
-  il@(IdLabel name cafInfo idLabelInfo)
-    | isInternalName name
-    -> IdLabel . setNameUnique name <$> f (nameUnique name) <*> pure cafInfo <*> pure idLabelInfo
-    | otherwise
-    -> pure il
+  il@(IdLabel name cafInfo idLabelInfo) -> IdLabel . setNameUnique name <$> f (nameUnique name) <*> pure cafInfo <*> pure idLabelInfo
   cl at CmmLabel{} -> pure cl
   -- ROMES:TODO: what about `RtsApFast NonDetFastString`?
   RtsLabel rtsLblInfo -> pure $ RtsLabel rtsLblInfo


=====================================
compiler/GHC/Cmm/Pipeline.hs
=====================================
@@ -78,7 +78,7 @@ cpsTop logger platform cfg proc =
       --
       CmmProc h l v g <- {-# SCC "cmmCfgOpts(1)" #-}
            return $ cmmCfgOptsProc splitting_proc_points proc
-      dump Opt_D_dump_cmm_cfg "Post control-flow optimisations" g
+      dump Opt_D_dump_cmm_cfg "Post control-flow optimisations (1)" g
 
       let !TopInfo {stack_info=StackInfo { arg_space = entry_off
                                          , do_layout = do_layout }} = h
@@ -168,7 +168,7 @@ cpsTop logger platform cfg proc =
                     else g
       g <- return $ map (removeUnreachableBlocksProc platform) g
            -- See Note [unreachable blocks]
-      dumps Opt_D_dump_cmm_cfg "Post control-flow optimisations" g
+      dumps Opt_D_dump_cmm_cfg "Post control-flow optimisations (2)" g
 
       return (Left (cafEnv, g))
 


=====================================
compiler/GHC/Cmm/UniqueRenamer.hs
=====================================
@@ -91,11 +91,7 @@ detRenameCLabel = mapInternalNonDetUniques renameDetUniq
 
 -- | We want to rename uniques in Ids, but ONLY internal ones.
 detRenameId :: Id -> DetRnM Id
-detRenameId i
-    | isInternalName (idName i)
-    = setIdUnique i <$> renameDetUniq (getUnique i)
-    | otherwise
-    = pure i
+detRenameId i = setIdUnique i <$> renameDetUniq (getUnique i)
 
 --------------------------------------------------------------------------------
 -- Traversals
@@ -114,7 +110,9 @@ instance UniqRenamable CLabel where
   uniqRename = detRenameCLabel
 
 instance UniqRenamable LocalReg where
-  uniqRename (LocalReg uq t) = LocalReg <$> renameDetUniq uq <*> pure t
+  -- uniqRename (LocalReg uq t) = LocalReg <$> renameDetUniq uq <*> pure t
+  uniqRename (LocalReg uq t) = pure $ LocalReg uq t
+    -- ROMES:TODO: This has unique r1, we're debugging. this may still be a source of non determinism.
 
 instance UniqRenamable Label where
   uniqRename lbl = mkHooplLabel . getKey <$> renameDetUniq (getUnique lbl)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/56226ec23e89047a7e7566b5f52ac6b1b3fa28ce...d910fe193fce99651fb9379a44dcbb61a8c91bfd

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/56226ec23e89047a7e7566b5f52ac6b1b3fa28ce...d910fe193fce99651fb9379a44dcbb61a8c91bfd
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/20240626/6ac8b62f/attachment-0001.html>


More information about the ghc-commits mailing list