module LlvmMangler ( llvmFixupAsm ) where
import DynFlags ( DynFlags )
import ErrUtils ( showPass )
import LlvmCodeGen.Ppr ( infoSection )
import Control.Exception
import Control.Monad ( when )
import qualified Data.ByteString.Char8 as B
import Data.Char
import System.IO
import Data.List ( sortBy )
import Data.Function ( on )
#if x86_64_TARGET_ARCH
#define REWRITE_AVX
#endif
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 :: Int
infoLen = B.length infoSec
isType :: B.ByteString -> Bool
isType = B.isPrefixOf (B.pack "\t.type")
type Section = (B.ByteString, B.ByteString)
llvmFixupAsm :: DynFlags -> FilePath -> FilePath -> IO ()
llvmFixupAsm dflags f1 f2 = do
showPass dflags "LLVM Mangler"
r <- openBinaryFile f1 ReadMode
w <- openBinaryFile f2 WriteMode
ss <- readSections r w
hClose r
let fixed = (map rewriteAVX . fixTables) ss
mapM_ (writeSection w) fixed
hClose w
return ()
rewriteSymType :: B.ByteString -> B.ByteString
rewriteSymType s =
foldl (\s' (typeFunc,typeObj)->replace typeFunc typeObj s') s types
where
types = [ (B.pack "@function", B.pack "@object")
, (B.pack "%function", B.pack "%object")
]
readSections :: Handle -> Handle -> IO [Section]
readSections r w = go B.empty [] []
where
go hdr ss ls = do
e_l <- (try (B.hGetLine r))::IO (Either IOError B.ByteString)
let (tys, ls') = span isType ls
cts = rewriteSymType $ B.intercalate newLine $ reverse ls'
let finishSection
| infoSec `B.isInfixOf` hdr =
cts `seq` return $ (hdr, cts):ss
| otherwise =
writeSection w (hdr, cts) >> return ss
case e_l of
Right l | l == syntaxUnified
-> finishSection >>= \ss' -> writeSection w (l, B.empty)
>> go B.empty ss' tys
| any (`B.isPrefixOf` l) [secStmt, textStmt, dataStmt]
-> finishSection >>= \ss' -> go l ss' tys
| otherwise
-> go hdr ss (l:ls)
Left _ -> finishSection >>= \ss' -> return (reverse ss')
writeSection :: Handle -> Section -> IO ()
writeSection w (hdr, cts) = do
when (not $ B.null hdr) $
B.hPutStrLn w hdr
B.hPutStrLn w cts
#if REWRITE_AVX
rewriteAVX :: Section -> Section
rewriteAVX = rewriteVmovaps . rewriteVmovdqa
rewriteVmovdqa :: Section -> Section
rewriteVmovdqa = rewriteInstructions vmovdqa vmovdqu
where
vmovdqa, vmovdqu :: B.ByteString
vmovdqa = B.pack "vmovdqa"
vmovdqu = B.pack "vmovdqu"
rewriteVmovap :: Section -> Section
rewriteVmovap = rewriteInstructions vmovap vmovup
where
vmovap, vmovup :: B.ByteString
vmovap = B.pack "vmovap"
vmovup = B.pack "vmovup"
rewriteInstructions :: B.ByteString -> B.ByteString -> Section -> Section
rewriteInstructions matchBS replaceBS (hdr, cts) =
(hdr, replace matchBS replaceBS cts)
#else /* !REWRITE_AVX */
rewriteAVX :: Section -> Section
rewriteAVX = id
#endif /* !REWRITE_SSE */
replace :: B.ByteString -> B.ByteString -> B.ByteString -> B.ByteString
replace matchBS replaceBS = loop
where
loop :: B.ByteString -> B.ByteString
loop cts =
case B.breakSubstring matchBS cts of
(hd,tl) | B.null tl -> hd
| otherwise -> hd `B.append` replaceBS `B.append`
loop (B.drop (B.length matchBS) tl)
fixTables :: [Section] -> [Section]
fixTables ss = map strip sorted
where
extractIx hdr
| B.null a = 0
| otherwise = 1 + readInt (B.takeWhile isDigit $ B.drop infoLen a)
where (_,a) = B.breakSubstring infoSec hdr
indexed = zip (map (extractIx . fst) ss) ss
sorted = map snd $ sortBy (compare `on` fst) indexed
strip (hdr, cts)
| infoSec `B.isInfixOf` hdr = (textStmt, cts)
| otherwise = (hdr, cts)
readInt :: B.ByteString -> Int
readInt str | B.all isDigit str = (read . B.unpack) str
| otherwise = error $ "LLvmMangler Cannot read " ++ show str
++ " as it's not an Int"