File ghc-avoid-empty-llvm-used-definitions.patch of Package ghc

git-author:    Geoffrey Mainland <gmainlan@…> (06/12/13 13:31:49)
git-committer: Geoffrey Mainland <gmainlan@…> (06/12/13 13:31:49)
Message:
    Avoid generating empty llvm.used definitions.

    LLVM 3.3rc3 complains when the llvm.used global is an empty array, so don't
    define llvm.used at all when it would be empty.
--

Index: ghc-7.6.3/compiler/llvmGen/LlvmCodeGen.hs
===================================================================
--- ghc-7.6.3.orig/compiler/llvmGen/LlvmCodeGen.hs
+++ ghc-7.6.3/compiler/llvmGen/LlvmCodeGen.hs
@@ -112,19 +112,19 @@ cmmProcLlvmGens :: DynFlags -> BufHandle
       -> [[LlvmVar]] -- ^ info tables that need to be marked as 'used'
       -> IO ()
 
-cmmProcLlvmGens _ _ _ _ [] _ []
-  = return ()
-
 cmmProcLlvmGens dflags h _ _ [] _ ivars
-  = let ivars' = concat ivars
-        cast x = LMBitc (LMStaticPointer (pVarLift x)) i8Ptr
-        ty     = (LMArray (length ivars') i8Ptr)
-        usedArray = LMStaticArray (map cast ivars') ty
-        lmUsed = (LMGlobalVar (fsLit "llvm.used") ty Appending
-                  (Just $ fsLit "llvm.metadata") Nothing False, Just usedArray)
-    in Prt.bufLeftRender h $ {-# SCC "llvm_used_ppr" #-}
-                             withPprStyleDoc dflags (mkCodeStyle CStyle) $
-                             pprLlvmData ([lmUsed], [])
+    | null ivars' = return ()
+    | otherwise   = Prt.bufLeftRender h $
+                        {-# SCC "llvm_used_ppr" #-}
+                        withPprStyleDoc dflags (mkCodeStyle CStyle) $
+                        pprLlvmData ([lmUsed], [])
+  where
+    ivars' = concat ivars
+    cast x = LMBitc (LMStaticPointer (pVarLift x)) i8Ptr
+    ty     = (LMArray (length ivars') i8Ptr)
+    usedArray = LMStaticArray (map cast ivars') ty
+    lmUsed = (LMGlobalVar (fsLit "llvm.used") ty Appending
+              (Just $ fsLit "llvm.metadata") Nothing False, Just usedArray)
 
 cmmProcLlvmGens dflags h us env ((CmmData _ _) : cmms) count ivars
  = cmmProcLlvmGens dflags h us env cmms count ivars
openSUSE Build Service is sponsored by