[Git][ghc/ghc][wip/T22010] Use Word64 for hoopl labels
Jaro Reinders (@Noughtmare)
gitlab at gitlab.haskell.org
Thu Jun 22 07:33:05 UTC 2023
Jaro Reinders pushed to branch wip/T22010 at Glasgow Haskell Compiler / GHC
Commits:
783893e1 by Jaro Reinders at 2023-06-22T09:32:59+02:00
Use Word64 for hoopl labels
- - - - -
3 changed files:
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/Dataflow/Collections.hs
- compiler/GHC/Cmm/Dataflow/Label.hs
Changes:
=====================================
compiler/GHC/Cmm/BlockId.hs
=====================================
@@ -34,8 +34,7 @@ compilation unit in which it appears.
type BlockId = Label
mkBlockId :: Unique -> BlockId
-mkBlockId unique = mkHooplLabel $ fromIntegral $ getKey unique
--- TODO: should BlockIds also use Word64?
+mkBlockId unique = mkHooplLabel $ getKey unique
newBlockId :: MonadUnique m => m BlockId
newBlockId = mkBlockId <$> getUniqueM
=====================================
compiler/GHC/Cmm/Dataflow/Collections.hs
=====================================
@@ -12,10 +12,11 @@ module GHC.Cmm.Dataflow.Collections
import GHC.Prelude
-import qualified Data.IntMap.Strict as M
-import qualified Data.IntSet as S
+import qualified GHC.Data.Word64Map.Strict as M
+import qualified GHC.Data.Word64Set as S
import Data.List (foldl1')
+import Data.Word (Word64)
class IsSet set where
type ElemOf set
@@ -107,10 +108,10 @@ mapUnions maps = foldl1' mapUnion maps
-- Basic instances
-----------------------------------------------------------------------------
-newtype UniqueSet = US S.IntSet deriving (Eq, Ord, Show, Semigroup, Monoid)
+newtype UniqueSet = US S.Word64Set deriving (Eq, Ord, Show, Semigroup, Monoid)
instance IsSet UniqueSet where
- type ElemOf UniqueSet = Int
+ type ElemOf UniqueSet = Word64
setNull (US s) = S.null s
setSize (US s) = S.size s
@@ -133,11 +134,11 @@ instance IsSet UniqueSet where
setElems (US s) = S.elems s
setFromList ks = US (S.fromList ks)
-newtype UniqueMap v = UM (M.IntMap v)
+newtype UniqueMap v = UM (M.Word64Map v)
deriving (Eq, Ord, Show, Functor, Foldable, Traversable)
instance IsMap UniqueMap where
- type KeyOf UniqueMap = Int
+ type KeyOf UniqueMap = Word64
mapNull (UM m) = M.null m
mapSize (UM m) = M.size m
=====================================
compiler/GHC/Cmm/Dataflow/Label.hs
=====================================
@@ -22,16 +22,17 @@ import GHC.Cmm.Dataflow.Collections
import GHC.Types.Unique (Uniquable(..))
import GHC.Data.TrieMap
+import Data.Word (Word64)
-----------------------------------------------------------------------------
-- Label
-----------------------------------------------------------------------------
-newtype Label = Label { lblToUnique :: Int }
+newtype Label = Label { lblToUnique :: Word64 }
deriving (Eq, Ord)
-mkHooplLabel :: Int -> Label
+mkHooplLabel :: Word64 -> Label
mkHooplLabel = Label
instance Show Label where
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/783893e198366718f52f361954a77598bfdb8c80
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/783893e198366718f52f361954a77598bfdb8c80
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/20230622/d82904c3/attachment-0001.html>
More information about the ghc-commits
mailing list