module LlvmCodeGen.Ppr (
pprLlvmHeader, pprLlvmCmmTop, pprLlvmData, infoSection, iTableSuf
) where
#include "HsVersions.h"
import Llvm
import LlvmCodeGen.Base
import LlvmCodeGen.Data
import CLabel
import Cmm
import FastString
import qualified Outputable
import Pretty
import Unique
moduleLayout :: Doc
moduleLayout =
#if i386_TARGET_ARCH
#if darwin_TARGET_OS
text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:32:64-f32:32:32-f64:32:64-v64:64:64-v128:128:128-a0:0:64-f80:128:128-n8:16:32\""
$+$ text "target triple = \"i386-apple-darwin9.8\""
#elif mingw32_TARGET_OS
text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-f80:128:128-v64:64:64-v128:128:128-a0:0:64-f80:32:32-n8:16:32\""
$+$ text "target triple = \"i686-pc-win32\""
#else /* Linux */
text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:32:64-f32:32:32-f64:32:64-v64:64:64-v128:128:128-a0:0:64-f80:32:32-n8:16:32\""
$+$ text "target triple = \"i386-pc-linux-gnu\""
#endif
#elif x86_64_TARGET_ARCH
#if darwin_TARGET_OS
text "target datalayout = \"e-p:64:64:64-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-v64:64:64-v128:128:128-a0:0:64-s0:64:64-f80:128:128-n8:16:32:64\""
$+$ text "target triple = \"x86_64-apple-darwin10.0.0\""
#else /* Linux */
text "target datalayout = \"e-p:64:64:64-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-v64:64:64-v128:128:128-a0:0:64-s0:64:64-f80:128:128-n8:16:32:64\""
$+$ text "target triple = \"x86_64-linux-gnu\""
#endif
#else /* Not x86 */
empty
#endif
pprLlvmHeader :: Doc
pprLlvmHeader = moduleLayout
pprLlvmData :: LlvmData -> Doc
pprLlvmData (globals, types) =
let tryConst (v, Just s ) = ppLlvmGlobal (v, Just s)
tryConst g@(_, Nothing) = ppLlvmGlobal g
ppLlvmTys (LMAlias a) = ppLlvmAlias a
ppLlvmTys (LMFunction f) = ppLlvmFunctionDecl f
ppLlvmTys _other = empty
types' = vcat $ map ppLlvmTys types
globals' = vcat $ map tryConst globals
in types' $+$ globals'
pprLlvmCmmTop :: LlvmEnv -> Int -> LlvmCmmTop -> (Doc, [LlvmVar])
pprLlvmCmmTop _ _ (CmmData _ lmdata)
= (vcat $ map pprLlvmData lmdata, [])
pprLlvmCmmTop env count (CmmProc info lbl _ (ListGraph blks))
= let static = CmmDataLabel lbl : info
(idoc, ivar) = if not (null info)
then pprInfoTable env count lbl static
else (empty, [])
in (idoc $+$ (
let sec = mkLayoutSection (count + 1)
(lbl',sec') = if not (null info)
then (entryLblToInfoLbl lbl, sec)
else (lbl, Nothing)
link = if externallyVisibleCLabel lbl'
then ExternallyVisible
else Internal
lmblocks = map (\(BasicBlock id stmts) ->
LlvmBlock (getUnique id) stmts) blks
fun = mkLlvmFunc lbl' link sec' lmblocks
in ppLlvmFunction fun
), ivar)
pprInfoTable :: LlvmEnv -> Int -> CLabel -> [CmmStatic] -> (Doc, [LlvmVar])
pprInfoTable env count lbl stat
= let unres = genLlvmData (Text, stat)
(_, (ldata, ltypes)) = resolveLlvmData env unres
setSection ((LMGlobalVar _ ty l _ _ c), d)
= let sec = mkLayoutSection count
ilabel = strCLabel_llvm (entryLblToInfoLbl lbl)
`appendFS` fsLit iTableSuf
gv = LMGlobalVar ilabel ty l sec llvmInfAlign c
v = if l == Internal then [gv] else []
in ((gv, d), v)
setSection v = (v,[])
(ldata', llvmUsed) = setSection (last ldata)
in if length ldata /= 1
then Outputable.panic "LlvmCodeGen.Ppr: invalid info table!"
else (pprLlvmData ([ldata'], ltypes), llvmUsed)
iTableSuf :: String
iTableSuf = "_itable"
mkLayoutSection :: Int -> LMSection
mkLayoutSection n
= Just (fsLit $ infoSection ++ show n
#if darwin_TARGET_OS
)
#else
++ "#")
#endif
infoSection :: String
#if darwin_TARGET_OS
infoSection = "__STRIP,__me"
#else
infoSection = ".text; .text "
#endif