module LlvmCodeGen.Ppr (
pprLlvmHeader, pprLlvmCmmDecl, pprLlvmData, infoSection, iTableSuf
) where
#include "HsVersions.h"
import Llvm
import LlvmCodeGen.Base
import LlvmCodeGen.Data
import CLabel
import Cmm
import Platform
import FastString
import Outputable
import Unique
pprLlvmHeader :: SDoc
pprLlvmHeader = moduleLayout
moduleLayout :: SDoc
moduleLayout = sdocWithPlatform $ \platform ->
case platform of
Platform { platformArch = ArchX86, platformOS = OSDarwin } ->
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\""
Platform { platformArch = ArchX86, platformOS = OSMinGW32 } ->
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\""
Platform { platformArch = ArchX86, platformOS = OSLinux } ->
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\""
Platform { platformArch = ArchX86_64, platformOS = OSDarwin } ->
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\""
Platform { platformArch = ArchX86_64, platformOS = OSLinux } ->
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\""
Platform { platformArch = ArchARM {}, platformOS = OSLinux } ->
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-v64:64:64-v128:64:128-a0:0:64-n32\""
$+$ text "target triple = \"arm-unknown-linux-gnueabi\""
Platform { platformArch = ArchARM {}, platformOS = OSAndroid } ->
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-v64:64:64-v128:64:128-a0:0:64-n32\""
$+$ text "target triple = \"arm-unknown-linux-androideabi\""
Platform { platformArch = ArchARM {}, platformOS = OSQNXNTO } ->
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-v64:64:64-v128:64:128-a0:0:64-n32\""
$+$ text "target triple = \"arm-unknown-nto-qnx8.0.0eabi\""
Platform { platformArch = ArchARM {}, platformOS = OSiOS } ->
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-v64:64:64-v128:64:128-a0:0:64-n32\""
$+$ text "target triple = \"arm-apple-darwin10\""
Platform { platformArch = ArchX86, platformOS = OSiOS } ->
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-darwin11\""
Platform { platformArch = ArchARM64, platformOS = OSiOS } ->
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-n32:64-S128\""
$+$ text "target triple = \"arm64-apple-ios7.0.0\""
_ ->
empty
pprLlvmData :: LlvmData -> SDoc
pprLlvmData (globals, types) =
let ppLlvmTys (LMAlias a) = ppLlvmAlias a
ppLlvmTys (LMFunction f) = ppLlvmFunctionDecl f
ppLlvmTys _other = empty
types' = vcat $ map ppLlvmTys types
globals' = ppLlvmGlobals globals
in types' $+$ globals'
pprLlvmCmmDecl :: Int -> LlvmCmmDecl -> LlvmM (SDoc, [LlvmVar])
pprLlvmCmmDecl _ (CmmData _ lmdata)
= return (vcat $ map pprLlvmData lmdata, [])
pprLlvmCmmDecl count (CmmProc mb_info entry_lbl live (ListGraph blks))
= do (idoc, ivar) <- case mb_info of
Nothing -> return (empty, [])
Just (Statics info_lbl dat)
-> pprInfoTable count info_lbl (Statics entry_lbl dat)
let sec = mkLayoutSection (count + 1)
(lbl',sec') = case mb_info of
Nothing -> (entry_lbl, Nothing)
Just (Statics info_lbl _) -> (info_lbl, sec)
link = if externallyVisibleCLabel lbl'
then ExternallyVisible
else Internal
lmblocks = map (\(BasicBlock id stmts) ->
LlvmBlock (getUnique id) stmts) blks
fun <- mkLlvmFunc live lbl' link sec' lmblocks
let name = decName $ funcDecl fun
defName = name `appendFS` fsLit "$def"
funcDecl' = (funcDecl fun) { decName = defName }
fun' = fun { funcDecl = funcDecl' }
funTy = LMFunction funcDecl'
funVar = LMGlobalVar name
(LMPointer funTy)
link
Nothing
Nothing
Alias
defVar = LMGlobalVar defName
(LMPointer funTy)
(funcLinkage funcDecl')
(funcSect fun)
(funcAlign funcDecl')
Alias
alias = LMGlobal funVar
(Just $ LMBitc (LMStaticPointer defVar)
(LMPointer $ LMInt 8))
return (ppLlvmGlobal alias $+$ idoc $+$ ppLlvmFunction fun', ivar)
pprInfoTable :: Int -> CLabel -> CmmStatics -> LlvmM (SDoc, [LlvmVar])
pprInfoTable count info_lbl stat
= do (ldata, ltypes) <- genLlvmData (Text, stat)
dflags <- getDynFlags
platform <- getLlvmPlatform
let setSection :: LMGlobal -> LlvmM (LMGlobal, [LlvmVar])
setSection (LMGlobal (LMGlobalVar _ ty l _ _ c) d) = do
lbl <- strCLabel_llvm info_lbl
let sec = mkLayoutSection count
ilabel = lbl `appendFS` fsLit iTableSuf
gv = LMGlobalVar ilabel ty l sec (llvmInfAlign dflags) c
v = if (platformHasSubsectionsViaSymbols platform
&& l == ExternallyVisible)
|| l == Internal
then [gv]
else []
funInsert ilabel ty
return (LMGlobal gv d, v)
setSection v = return (v,[])
(ldata', llvmUsed) <- unzip `fmap` mapM setSection ldata
ldata'' <- mapM aliasify ldata'
let modUsedLabel (LMGlobalVar name ty link sect align const) =
LMGlobalVar (name `appendFS` fsLit "$def") ty link sect align const
modUsedLabel v = v
llvmUsed' = map modUsedLabel $ concat llvmUsed
return (pprLlvmData (concat ldata'', ltypes), llvmUsed')
iTableSuf :: String
iTableSuf = "_itable"
mkLayoutSection :: Int -> LMSection
mkLayoutSection n
= Just (fsLit $ infoSection ++ show n)
infoSection :: String
infoSection = "X98A__STRIP,__me"