module PprCmmDecl
( writeCmms, pprCmms, pprCmmGroup, pprSection, pprStatic
)
where
import GhcPrelude
import PprCmmExpr
import Cmm
import DynFlags
import Outputable
import FastString
import Data.List
import System.IO
import qualified Data.ByteString as BS
pprCmms :: (Outputable info, Outputable g)
=> [GenCmmGroup CmmStatics info g] -> SDoc
pprCmms cmms = pprCode CStyle (vcat (intersperse separator $ map ppr cmms))
where
separator = space $$ text "-------------------" $$ space
writeCmms :: (Outputable info, Outputable g)
=> DynFlags -> Handle -> [GenCmmGroup CmmStatics info g] -> IO ()
writeCmms dflags handle cmms = printForC dflags handle (pprCmms cmms)
instance (Outputable d, Outputable info, Outputable i)
=> Outputable (GenCmmDecl d info i) where
ppr t = pprTop t
instance Outputable CmmStatics where
ppr = pprStatics
instance Outputable CmmStatic where
ppr = pprStatic
instance Outputable CmmInfoTable where
ppr = pprInfoTable
pprCmmGroup :: (Outputable d, Outputable info, Outputable g)
=> GenCmmGroup d info g -> SDoc
pprCmmGroup tops
= vcat $ intersperse blankLine $ map pprTop tops
pprTop :: (Outputable d, Outputable info, Outputable i)
=> GenCmmDecl d info i -> SDoc
pprTop (CmmProc info lbl live graph)
= vcat [ ppr lbl <> lparen <> rparen <+> lbrace <+> text "// " <+> ppr live
, nest 8 $ lbrace <+> ppr info $$ rbrace
, nest 4 $ ppr graph
, rbrace ]
pprTop (CmmData section ds) =
(hang (pprSection section <+> lbrace) 4 (ppr ds))
$$ rbrace
pprInfoTable :: CmmInfoTable -> SDoc
pprInfoTable (CmmInfoTable { cit_lbl = lbl, cit_rep = rep
, cit_prof = prof_info
, cit_srt = srt })
= vcat [ text "label: " <> ppr lbl
, text "rep: " <> ppr rep
, case prof_info of
NoProfilingInfo -> empty
ProfilingInfo ct cd ->
vcat [ text "type: " <> text (show (BS.unpack ct))
, text "desc: " <> text (show (BS.unpack cd)) ]
, text "srt: " <> ppr srt ]
instance Outputable ForeignHint where
ppr NoHint = empty
ppr SignedHint = quotes(text "signed")
ppr AddrHint = (text "PtrHint")
pprStatics :: CmmStatics -> SDoc
pprStatics (Statics lbl ds) = vcat ((ppr lbl <> colon) : map ppr ds)
pprStatic :: CmmStatic -> SDoc
pprStatic s = case s of
CmmStaticLit lit -> nest 4 $ text "const" <+> pprLit lit <> semi
CmmUninitialised i -> nest 4 $ text "I8" <> brackets (int i)
CmmString s' -> nest 4 $ text "I8[]" <+> text (show s')
pprSection :: Section -> SDoc
pprSection (Section t suffix) =
section <+> doubleQuotes (pprSectionType t <+> char '.' <+> ppr suffix)
where
section = text "section"
pprSectionType :: SectionType -> SDoc
pprSectionType s = doubleQuotes (ptext t)
where
t = case s of
Text -> sLit "text"
Data -> sLit "data"
ReadOnlyData -> sLit "readonly"
ReadOnlyData16 -> sLit "readonly16"
RelocatableReadOnlyData
-> sLit "relreadonly"
UninitialisedData -> sLit "uninitialised"
CString -> sLit "cstring"
OtherSection s' -> sLit s'