[Git][ghc/ghc][wip/llvm-initializers] CmmToLlvm: Don't aliasify builtin LLVM variables

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Fri Aug 12 15:39:55 UTC 2022



Ben Gamari pushed to branch wip/llvm-initializers at Glasgow Haskell Compiler / GHC


Commits:
28d03900 by Ben Gamari at 2022-08-12T11:37:51-04:00
CmmToLlvm: Don't aliasify builtin LLVM variables

Our aliasification logic would previously turn builtin LLVM variables
into aliases, which apparently confuses LLVM. This manifested in
initializers failing to be emitted, resulting in many profiling failures
with the LLVM backend.

- - - - -


1 changed file:

- compiler/GHC/CmmToLlvm/Base.hs


Changes:

=====================================
compiler/GHC/CmmToLlvm/Base.hs
=====================================
@@ -58,7 +58,7 @@ import GHC.Utils.Logger
 
 import Data.Maybe (fromJust)
 import Control.Monad (ap)
-import Data.List (sortBy, groupBy)
+import Data.List (sortBy, groupBy, isPrefixOf)
 import Data.Ord (comparing)
 
 -- ----------------------------------------------------------------------------
@@ -504,6 +504,12 @@ generateExternDecls = do
   modifyEnv $ \env -> env { envAliases = emptyUniqSet }
   return (concat defss, [])
 
+-- | Is a variable one of the special @$llvm@ globals?
+isBuiltinLlvmVar :: LlvmVar -> Bool
+isBuiltinLlvmVar (LMGlobalVar lbl _ _ _ _ _) =
+    "$llvm" `isPrefixOf` unpackFS lbl
+isBuiltinLlvmVar _ = False
+
 -- | Here we take a global variable definition, rename it with a
 -- @$def@ suffix, and generate the appropriate alias.
 aliasify :: LMGlobal -> LlvmM [LMGlobal]
@@ -511,8 +517,9 @@ aliasify :: LMGlobal -> LlvmM [LMGlobal]
 -- Here we obtain the indirectee's precise type and introduce
 -- fresh aliases to both the precise typed label (lbl$def) and the i8*
 -- typed (regular) label of it with the matching new names.
-aliasify (LMGlobal (LMGlobalVar lbl ty at LMAlias{} link sect align Alias)
-                   (Just orig)) = do
+aliasify (LMGlobal var@(LMGlobalVar lbl ty at LMAlias{} link sect align Alias)
+                   (Just orig))
+  | not $ isBuiltinLlvmVar var = do
     let defLbl = llvmDefLabel lbl
         LMStaticPointer (LMGlobalVar origLbl _ oLnk Nothing Nothing Alias) = orig
         defOrigLbl = llvmDefLabel origLbl
@@ -525,7 +532,8 @@ aliasify (LMGlobal (LMGlobalVar lbl ty at LMAlias{} link sect align Alias)
     pure [ LMGlobal (LMGlobalVar defLbl ty link sect align Alias) (Just defOrig)
          , LMGlobal (LMGlobalVar lbl i8Ptr link sect align Alias) (Just orig')
          ]
-aliasify (LMGlobal var val) = do
+aliasify (LMGlobal var val)
+  | not $ isBuiltinLlvmVar var = do
     let LMGlobalVar lbl ty link sect align const = var
 
         defLbl = llvmDefLabel lbl
@@ -543,6 +551,7 @@ aliasify (LMGlobal var val) = do
     return [ LMGlobal defVar val
            , LMGlobal aliasVar (Just aliasVal)
            ]
+aliasify global = pure [global]
 
 -- Note [Llvm Forward References]
 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -601,3 +610,6 @@ aliasify (LMGlobal var val) = do
 -- away with casting the alias to the desired type in @getSymbolPtr@
 -- and instead just emit a reference to the definition symbol directly.
 -- This is the @Just@ case in @getSymbolPtr at .
+--
+-- Note that we must take care not to turn LLVM's builtin variables into
+-- aliases (e.g. $llvm.global_ctors) since this confuses LLVM.



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28d039007d05eb4bf2cde6457b66bc9a2182fdc3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28d039007d05eb4bf2cde6457b66bc9a2182fdc3
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/20220812/f74d744c/attachment-0001.html>


More information about the ghc-commits mailing list