[Git][ghc/ghc][wip/romes/12935] cleanup
Rodrigo Mesquita (@alt-romes)
gitlab at gitlab.haskell.org
Mon Jul 1 14:21:08 UTC 2024
Rodrigo Mesquita pushed to branch wip/romes/12935 at Glasgow Haskell Compiler / GHC
Commits:
7cf90ba5 by Rodrigo Mesquita at 2024-07-01T15:21:01+01:00
cleanup
- - - - -
3 changed files:
- compiler/GHC/Cmm/UniqueRenamer.hs
- testsuite/tests/determinism/object/check-standalone.sh
- testsuite/tests/determinism/object/check.sh
Changes:
=====================================
compiler/GHC/Cmm/UniqueRenamer.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE LambdaCase, MagicHash, UnboxedTuples, PatternSynonyms, ExplicitNamespaces #-}
+{-# LANGUAGE LambdaCase, MagicHash, UnboxedTuples, PatternSynonyms, ExplicitNamespaces, TypeFamilies #-}
module GHC.Cmm.UniqueRenamer
( detRenameUniques
, UniqDSM, runUniqueDSM
@@ -23,8 +23,6 @@ import GHC.Types.Unique
import GHC.Types.Unique.FM
import GHC.Utils.Outputable as Outputable
import Data.Tuple (swap)
-import qualified Data.Map as M
-import qualified Data.Set as S
import GHC.Types.Id
{-
@@ -72,7 +70,7 @@ renameDetUniq uq = do
Nothing -> do
new_w <- gets supply -- New deterministic unique in this `DetRnM`
let (tag, _) = unpkUnique uq
- det_uniq = mkUnique 'Q' new_w
+ det_uniq = mkUnique tag new_w
modify' (\DetUniqFM{mapping, supply} ->
-- Update supply and mapping
DetUniqFM
@@ -184,7 +182,7 @@ instance UniqRenamable CmmLit where
CmmBlock bid -> CmmBlock <$> uniqRename bid
CmmHighStackMark -> pure CmmHighStackMark
--- TODO::: VERY BAD!!! This isn't deterministic since the key is non-deterministic thus the order in which we rename is non deterministic
+-- This is fine because LabelMap is backed by a deterministic UDFM
instance UniqRenamable a {- for 'Body' and on 'RawCmmStatics' -}
=> UniqRenamable (LabelMap a) where
uniqRename lm = mapFromListWith panicMapKeysNotInjective <$> traverse (\(l,x) -> (,) <$> uniqRename l <*> uniqRename x) (mapToList lm)
@@ -270,16 +268,6 @@ instance (UniqRenamable a) => UniqRenamable (Maybe a) where
uniqRename Nothing = pure Nothing
uniqRename (Just x) = Just <$> uniqRename x
--- TODO::: BAD!!! This won't be deterministic if the key is non-deterministic because the order in which we rename is non deterministic
-instance (Ord a, UniqRenamable a, UniqRenamable b) => UniqRenamable (M.Map a b) where
- uniqRename m = M.fromListWith panicMapKeysNotInjective <$> traverse (\(l,x) -> (,) <$> uniqRename l <*> uniqRename x) (M.toList m)
-
--- TODO::: BAD!!! This won't be deterministic if the key is non-deterministic because the order in which we rename is non deterministic
-instance (Ord a, UniqRenamable a) => UniqRenamable (S.Set a) where
- -- Because of renaming being injective the resulting set should have the same
- -- size as the intermediate list.
- uniqRename s = S.fromList <$> mapM uniqRename (S.toList s)
-
-- | Utility panic used by UniqRenamable instances for Map-like datatypes
panicMapKeysNotInjective :: a -> b -> c
panicMapKeysNotInjective _ _ = error "this should be impossible because the function which maps keys should be injective"
=====================================
testsuite/tests/determinism/object/check-standalone.sh
=====================================
@@ -9,5 +9,7 @@ fi
rm -rf objs1 objs2
cabal get Cabal-3.12.0.0
cabal build -w $1 --ghc-options="-fforce-recomp -j4 -ddump-to-file -ddump-asm -ddump-cmm -ddump-stg-final" --ghc-options=-odir=out1 Cabal
+# cabal build -w $1 --ghc-options="-fforce-recomp -j4" --ghc-options=-odir=out1 Cabal
cabal build -w $1 --ghc-options="-fforce-recomp -j4 -dinitial-unique=16777215 -dunique-increment=-1 -ddump-to-file -ddump-asm -ddump-cmm -ddump-stg-final" --ghc-options=-odir=out2 Cabal
+# cabal build -w $1 --ghc-options="-fforce-recomp -j4" --ghc-options=-odir=out2 Cabal
./check.sh darwin
=====================================
testsuite/tests/determinism/object/check.sh
=====================================
@@ -21,7 +21,7 @@ fi
S1=`find Cabal-3.12.0.0/out1 -name "*.o" | wc -l`
S2=`find Cabal-3.12.0.0/out2 -name "*.o" | wc -l`
-test $S1 > 0
+test $S1 > 0 || (echo "no files generated" && false)
test $S1 == $S2
# $1 = objects
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7cf90ba5694710b27b102837aa5ed2e0a6bd5640
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7cf90ba5694710b27b102837aa5ed2e0a6bd5640
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/20240701/0540d369/attachment-0001.html>
More information about the ghc-commits
mailing list