[Git][ghc/ghc][master] compiler: use zero cost coerce in hoopl setElems/mapToList
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: bedc1004 by Cheng Shao at 2025-08-26T09:31:18-04:00 compiler: use zero cost coerce in hoopl setElems/mapToList This patch is a follow-up of !14680 and changes setElems/mapToList in GHC/Cmm/Dataflow/Label to use coerce instead of mapping mkHooplLabel over the keys. - - - - - 1 changed file: - compiler/GHC/Cmm/Dataflow/Label.hs Changes: ===================================== compiler/GHC/Cmm/Dataflow/Label.hs ===================================== @@ -83,6 +83,7 @@ import GHC.Data.Word64Map.Strict (Word64Map) import qualified GHC.Data.Word64Map.Strict as M import GHC.Data.TrieMap +import Data.Coerce import Data.Word (Word64) @@ -164,7 +165,7 @@ setFoldr k z (LS s) = S.foldr (\v a -> k (mkHooplLabel v) a) z s {-# INLINE setElems #-} setElems :: LabelSet -> [Label] -setElems (LS s) = map mkHooplLabel (S.elems s) +setElems (LS s) = coerce $ S.elems s {-# INLINE setFromList #-} setFromList :: [Label] -> LabelSet @@ -272,7 +273,7 @@ mapKeys (LM m) = map (mkHooplLabel . fst) (M.toList m) {-# INLINE mapToList #-} mapToList :: LabelMap b -> [(Label, b)] -mapToList (LM m) = [(mkHooplLabel k, v) | (k, v) <- M.toList m] +mapToList (LM m) = coerce $ M.toList m {-# INLINE mapFromList #-} mapFromList :: [(Label, v)] -> LabelMap v View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bedc1004268f62e12cd1fbb8b0812db8... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bedc1004268f62e12cd1fbb8b0812db8... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)