[Git][ghc/ghc][master] perf: nameToCLabel: Directly manipulate ByteString rather than going via strings
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Thu Feb 6 04:17:56 UTC 2025
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
5622a14a by Matthew Pickering at 2025-02-05T23:17:27-05:00
perf: nameToCLabel: Directly manipulate ByteString rather than going via strings
`nameToCLabel` is called from `lookupHsSymbol` many times during
bytecode linking. We can save a lot of allocations and time by directly
manipulating the bytestrings rather than going via intermediate lists.
Before: 2GB allocation, 1.11s
After: 260MB allocation, 375ms
Fixes #25719
-------------------------
Metric Decrease:
MultiLayerModulesTH_OneShot
-------------------------
- - - - -
1 changed file:
- compiler/GHC/ByteCode/Linker.hs
Changes:
=====================================
compiler/GHC/ByteCode/Linker.hs
=====================================
@@ -1,6 +1,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -optc-DNON_POSIX_SOURCE #-}
--
-- (c) The University of Glasgow 2002-2006
@@ -210,9 +211,9 @@ linkFail who what
nameToCLabel :: Name -> String -> FastString
-nameToCLabel n suffix = mkFastString label
+nameToCLabel n suffix = mkFastStringByteString label
where
- encodeZ = zString . zEncodeFS
+ encodeZ = fastZStringToByteString . zEncodeFS
(Module pkgKey modName) = assert (isExternalName n) $ case nameModule n of
-- Primops are exported from GHC.Prim, their HValues live in GHC.PrimopWrappers
-- See Note [Primop wrappers] in GHC.Builtin.PrimOps.
@@ -222,11 +223,14 @@ nameToCLabel n suffix = mkFastString label
modulePart = encodeZ (moduleNameFS modName)
occPart = encodeZ $ occNameMangledFS (nameOccName n)
- label = concat
- [ if pkgKey == mainUnit then "" else packagePart ++ "_"
- , modulePart
- , '_':occPart
- , '_':suffix
+ label = mconcat $
+ [ packagePart `mappend` "_" | pkgKey /= mainUnit ]
+ ++
+ [modulePart
+ , "_"
+ , occPart
+ , "_"
+ , fromString suffix
]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5622a14a7a036ab36e28963a4fba826a5ac798a7
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5622a14a7a036ab36e28963a4fba826a5ac798a7
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/20250205/ac910df8/attachment-0001.html>
More information about the ghc-commits
mailing list