[Git][ghc/ghc][wip/mixed-uniqfm] FMs use Word64 now
Sebastian Graf (@sgraf812)
gitlab at gitlab.haskell.org
Wed Oct 18 16:08:47 UTC 2023
Sebastian Graf pushed to branch wip/mixed-uniqfm at Glasgow Haskell Compiler / GHC
Commits:
66833704 by Sebastian Graf at 2023-10-18T18:08:41+02:00
FMs use Word64 now
- - - - -
4 changed files:
- compiler/GHC/Data/Graph/UnVar.hs
- compiler/GHC/Types/Unique/DFM.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Var/Env.hs
Changes:
=====================================
compiler/GHC/Data/Graph/UnVar.hs
=====================================
@@ -31,7 +31,7 @@ module GHC.Data.Graph.UnVar
import GHC.Prelude
-import GHC.Types.Unique.FM( UniqFM, ufmToSet_Directly )
+import GHC.Types.Unique.FM( UniqFM, ufmToSet_Directly, getMixedKey, getUnmixedUnique )
import GHC.Types.Var
import GHC.Utils.Outputable
import GHC.Types.Unique
=====================================
compiler/GHC/Types/Unique/DFM.hs
=====================================
@@ -71,7 +71,7 @@ module GHC.Types.Unique.DFM (
import GHC.Prelude
-import GHC.Types.Unique ( Uniquable(..), Unique, getKey, mkUniqueGrimily )
+import GHC.Types.Unique ( Uniquable(..), Unique )
import GHC.Utils.Outputable
import qualified GHC.Data.Word64Map.Strict as MS
=====================================
compiler/GHC/Types/Unique/FM.hs
=====================================
@@ -122,7 +122,7 @@ newtype UniqFM key ele = UFM (M.Word64Map ele)
type role UniqFM representational representational -- Don't allow coerces over the key
-- | https://gist.github.com/degski/6e2069d6035ae04d5d6f64981c995ec2
-mix :: Word -> Int -> Int
+mix :: MS.Key -> MS.Key -> MS.Key
{-# INLINE mix #-}
mix k x = fromIntegral $ f $ g $ f $ g $ f $ fromIntegral x
where
@@ -130,26 +130,21 @@ mix k x = fromIntegral $ f $ g $ f $ g $ f $ fromIntegral x
g z = z * k
s = finiteBitSize k `shiftR` 1 -- 32 for 64 bit, 16 for 32 bit
-kFORWARD, kBACKWARD :: Word
+kFORWARD, kBACKWARD :: MS.Key
-- These are like "encryption" and "decryption" keys to mix
-#if UNIQUE_TAG_BITS == 8
kFORWARD = 0xD6E8FEB86659FD93
kBACKWARD = 0xCFEE444D8B59A89B
-#else
-kFORWARD = 0x45D9F3B
-kBACKWARD = 0x119DE1F3
-#endif
-enc, dec :: Int -> Int
+enc, dec :: MS.Key -> MS.Key
enc = mix kFORWARD
dec = mix kBACKWARD
{-# INLINE enc #-}
{-# INLINE dec #-}
-getMixedKey :: Unique -> Int
+getMixedKey :: Unique -> MS.Key
{-# NOINLINE getMixedKey #-}
getMixedKey = enc . getKey
-getUnmixedUnique :: Int -> Unique
+getUnmixedUnique :: MS.Key -> Unique
{-# NOINLINE getUnmixedUnique #-}
getUnmixedUnique = mkUniqueGrimily . dec
=====================================
compiler/GHC/Types/Var/Env.hs
=====================================
@@ -227,11 +227,11 @@ uniqAway' in_scope var
-- given 'InScopeSet'. This must be used very carefully since one can very easily
-- introduce non-unique 'Unique's this way. See Note [Local uniques].
unsafeGetFreshLocalUnique :: InScopeSet -> Unique
-unsafeGetFreshLocalUnique (InScope set) = go (getMixedKey (mkUniqueGrimily (sizeUniqSet set)))
+unsafeGetFreshLocalUnique (InScope set) = go (getMixedKey (mkUniqueGrimily (fromIntegral (sizeUniqSet set))))
where
go n
| let uniq = mkLocalUnique n
- , Nothing <- IntMap.lookup (getMixedKey $ uniq) (ufmToIntMap $ getUniqSet set)
+ , Nothing <- Word64Map.lookup (getMixedKey $ uniq) (ufmToIntMap $ getUniqSet set)
= uniq
| otherwise
= go (getMixedKey $ mkUniqueGrimily (n+1))
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/668337048d41d107865474939926620f83a0e6fd
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/668337048d41d107865474939926620f83a0e6fd
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/20231018/f847fec0/attachment-0001.html>
More information about the ghc-commits
mailing list