Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/af2b9ab54494dbafe21435654d1c044f760fef51

>---------------------------------------------------------------

commit af2b9ab54494dbafe21435654d1c044f760fef51
Author: David Terei <[email protected]>
Date:   Tue Nov 22 12:37:03 2011 -0800

    Clean up LLVM Mangler.

>---------------------------------------------------------------

 compiler/llvmGen/LlvmMangler.hs |   62 +++++++++------------------------------
 1 files changed, 14 insertions(+), 48 deletions(-)

diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs
index ff1dfa2..6ad9b72 100644
--- a/compiler/llvmGen/LlvmMangler.hs
+++ b/compiler/llvmGen/LlvmMangler.hs
@@ -1,19 +1,12 @@
-{-# OPTIONS -fno-warn-unused-binds #-}
 -- 
-----------------------------------------------------------------------------
 -- | GHC LLVM Mangler
 --
 -- This script processes the assembly produced by LLVM, rearranging the code
 -- so that an info table appears before its corresponding function.
 --
--- On OSX we also use it to fix up the stack alignment, which needs to be 16
--- byte aligned but always ends up off by word bytes because GHC sets it to
--- the 'wrong' starting value in the RTS.

>---------------------------------------------------------------

 
 module LlvmMangler ( llvmFixupAsm ) where
 
-#include "HsVersions.h"
-
 import DynFlags ( DynFlags )
 import ErrUtils ( showPass )
 import LlvmCodeGen.Ppr ( infoSection )
@@ -28,32 +21,23 @@ import Data.List ( sortBy )
 import Data.Function ( on )
 
 -- Magic Strings
-secStmt, infoSec, newLine, spInst, jmpInst, textStmt, dataStmt, syntaxUnified 
:: B.ByteString
-secStmt    = B.pack "\t.section\t"
-infoSec    = B.pack infoSection
-newLine    = B.pack "\n"
-jmpInst    = B.pack "\n\tjmp"
-textStmt   = B.pack "\t.text"
-dataStmt   = B.pack "\t.data"
+secStmt, infoSec, newLine, textStmt, dataStmt, syntaxUnified :: B.ByteString
+secStmt       = B.pack "\t.section\t"
+infoSec       = B.pack infoSection
+newLine       = B.pack "\n"
+textStmt      = B.pack "\t.text"
+dataStmt      = B.pack "\t.data"
 syntaxUnified = B.pack "\t.syntax unified"
 
-infoLen, labelStart, spFix :: Int
-infoLen    = B.length infoSec
-labelStart = B.length jmpInst
-
-#if x86_64_TARGET_ARCH
-spInst     = B.pack ", %rsp\n"
-spFix      = 8
-#else
-spInst     = B.pack ", %esp\n"
-spFix      = 4
-#endif
+infoLen :: Int
+infoLen = B.length infoSec
 
 -- Search Predicates
-eolPred, dollarPred, commaPred :: Char -> Bool
-eolPred    = ((==) '\n')
-dollarPred = ((==) '$')
-commaPred  = ((==) ',')
+isType :: B.ByteString -> Bool
+isType = B.isPrefixOf (B.pack "\t.type")
+
+-- section of a file in the form of (header line, contents)
+type Section = (B.ByteString, B.ByteString)
 
 -- | Read in assembly file and process
 llvmFixupAsm :: DynFlags -> FilePath -> FilePath -> IO ()
@@ -68,10 +52,7 @@ llvmFixupAsm dflags f1 f2 = do
     hClose w
     return ()
 
-type Section = (B.ByteString, B.ByteString)
-
--- | Splits the file contents into its sections. Each is returned as a
--- pair of the form (header line, contents lines)
+-- | Splits the file contents into its sections
 readSections :: Handle -> Handle -> IO [Section]
 readSections r w = go B.empty [] []
   where
@@ -82,7 +63,6 @@ readSections r w = go B.empty [] []
       -- the first directive of the *next* section, therefore we take
       -- it over to that section.
       let (tys, ls') = span isType ls
-          isType = B.isPrefixOf (B.pack "\t.type")
           cts = B.intercalate newLine $ reverse ls'
 
       -- Decide whether to directly output the section or append it
@@ -134,20 +114,6 @@ fixTables ss = map strip sorted
       | infoSec `B.isInfixOf` hdr = (textStmt, cts)
       | otherwise                 = (hdr, cts)
  
-{-|
-    Mac OS X requires that the stack be 16 byte aligned when making a function
-    call (only really required though when making a call that will pass through
-    the dynamic linker). The alignment isn't correctly generated by LLVM as
-    LLVM rightly assumes that the stack will be aligned to 16n + 12 on entry
-    (since the function call was 16 byte aligned and the return address should
-    have been pushed, so sub 4). GHC though since it always uses jumps keeps
-    the stack 16 byte aligned on both function calls and function entry.
-
-    We correct the alignment here for Mac OS X i386. The x86_64 target already
-    has the correct alignment since we keep the stack 16+8 aligned throughout
-    STG land for 64-bit targets.
--}
-
 -- | Read an int or error
 readInt :: B.ByteString -> Int
 readInt str | B.all isDigit str = (read . B.unpack) str



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to