module PprCmmDecl
( writeCmms, pprCmms, pprCmmGroup, pprSection, pprStatic
)
where
import CLabel
import PprCmmExpr
import Cmm
import Outputable
import Platform
import FastString
import Data.List
import System.IO
import SMRep
#include "../includes/rts/storage/FunTypes.h"
pprCmms :: (PlatformOutputable info, PlatformOutputable g)
=> Platform -> [GenCmmGroup CmmStatics info g] -> SDoc
pprCmms platform cmms = pprCode CStyle (vcat (intersperse separator $ map (pprPlatform platform) cmms))
where
separator = space $$ ptext (sLit "-------------------") $$ space
writeCmms :: (PlatformOutputable info, PlatformOutputable g)
=> Platform -> Handle -> [GenCmmGroup CmmStatics info g] -> IO ()
writeCmms platform handle cmms = printForC handle (pprCmms platform cmms)
instance (PlatformOutputable d, PlatformOutputable info, PlatformOutputable i)
=> PlatformOutputable (GenCmmDecl d info i) where
pprPlatform platform t = pprTop platform t
instance PlatformOutputable CmmStatics where
pprPlatform = pprStatics
instance PlatformOutputable CmmStatic where
pprPlatform = pprStatic
instance PlatformOutputable CmmInfoTable where
pprPlatform = pprInfoTable
pprCmmGroup :: (PlatformOutputable d,
PlatformOutputable info,
PlatformOutputable g)
=> Platform -> GenCmmGroup d info g -> SDoc
pprCmmGroup platform tops
= vcat $ intersperse blankLine $ map (pprTop platform) tops
pprTop :: (PlatformOutputable d, PlatformOutputable info, PlatformOutputable i)
=> Platform -> GenCmmDecl d info i -> SDoc
pprTop platform (CmmProc info lbl graph)
= vcat [ pprCLabel platform lbl <> lparen <> rparen
, nest 8 $ lbrace <+> pprPlatform platform info $$ rbrace
, nest 4 $ pprPlatform platform graph
, rbrace ]
pprTop platform (CmmData section ds) =
(hang (pprSection section <+> lbrace) 4 (pprPlatform platform ds))
$$ rbrace
pprInfoTable :: Platform -> CmmInfoTable -> SDoc
pprInfoTable _ CmmNonInfoTable
= empty
pprInfoTable platform
(CmmInfoTable { cit_lbl = lbl, cit_rep = rep
, cit_prof = prof_info
, cit_srt = _srt })
= vcat [ ptext (sLit "label:") <+> pprPlatform platform lbl
, ptext (sLit "rep:") <> ppr rep
, case prof_info of
NoProfilingInfo -> empty
ProfilingInfo ct cd -> vcat [ ptext (sLit "type:") <+> pprWord8String ct
, ptext (sLit "desc: ") <> pprWord8String cd ] ]
instance PlatformOutputable C_SRT where
pprPlatform _ (NoC_SRT) = ptext (sLit "_no_srt_")
pprPlatform platform (C_SRT label off bitmap)
= parens (pprPlatform platform label <> comma <> ppr off
<> comma <> text (show bitmap))
instance Outputable ForeignHint where
ppr NoHint = empty
ppr SignedHint = quotes(text "signed")
ppr AddrHint = (text "PtrHint")
instance PlatformOutputable ForeignHint where
pprPlatform _ = ppr
pprStatics :: Platform -> CmmStatics -> SDoc
pprStatics platform (Statics lbl ds) = vcat ((pprCLabel platform lbl <> colon) : map (pprPlatform platform) ds)
pprStatic :: Platform -> CmmStatic -> SDoc
pprStatic platform s = case s of
CmmStaticLit lit -> nest 4 $ ptext (sLit "const") <+> pprLit platform lit <> semi
CmmUninitialised i -> nest 4 $ text "I8" <> brackets (int i)
CmmString s' -> nest 4 $ text "I8[]" <+> text (show s')
pprSection :: Section -> SDoc
pprSection s = case s of
Text -> section <+> doubleQuotes (ptext (sLit "text"))
Data -> section <+> doubleQuotes (ptext (sLit "data"))
ReadOnlyData -> section <+> doubleQuotes (ptext (sLit "readonly"))
ReadOnlyData16 -> section <+> doubleQuotes (ptext (sLit "readonly16"))
RelocatableReadOnlyData
-> section <+> doubleQuotes (ptext (sLit "relreadonly"))
UninitialisedData -> section <+> doubleQuotes (ptext (sLit "uninitialised"))
OtherSection s' -> section <+> doubleQuotes (text s')
where
section = ptext (sLit "section")