{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
module GHC.Cmm (
CmmProgram, CmmGroup, CmmGroupSRTs, RawCmmGroup, GenCmmGroup,
CmmDecl, CmmDeclSRTs, GenCmmDecl(..),
CmmGraph, GenCmmGraph(..),
CmmBlock, RawCmmDecl,
Section(..), SectionType(..),
GenCmmStatics(..), type CmmStatics, type RawCmmStatics, CmmStatic(..),
SectionProtection(..), sectionProtection,
GenBasicBlock(..), blockId,
ListGraph(..), pprBBlock,
CmmTopInfo(..), CmmStackInfo(..), CmmInfoTable(..), topInfoTable,
ClosureTypeInfo(..),
ProfilingInfo(..), ConstrDescription,
module GHC.Cmm.Node,
module GHC.Cmm.Expr,
) where
import GHC.Prelude
import GHC.Types.Id
import GHC.Types.CostCentre
import GHC.Cmm.CLabel
import GHC.Cmm.BlockId
import GHC.Cmm.Node
import GHC.Runtime.Heap.Layout
import GHC.Cmm.Expr
import GHC.Cmm.Dataflow.Block
import GHC.Cmm.Dataflow.Collections
import GHC.Cmm.Dataflow.Graph
import GHC.Cmm.Dataflow.Label
import GHC.Utils.Outputable
import Data.ByteString (ByteString)
type CmmProgram = [CmmGroup]
type GenCmmGroup d h g = [GenCmmDecl d h g]
type CmmGroup = GenCmmGroup CmmStatics CmmTopInfo CmmGraph
type CmmGroupSRTs = GenCmmGroup RawCmmStatics CmmTopInfo CmmGraph
type RawCmmGroup = GenCmmGroup RawCmmStatics (LabelMap RawCmmStatics) CmmGraph
data GenCmmDecl d h g
= CmmProc
h
CLabel
[GlobalReg]
g
| CmmData
Section
d
deriving ((forall a b. (a -> b) -> GenCmmDecl d h a -> GenCmmDecl d h b)
-> (forall a b. a -> GenCmmDecl d h b -> GenCmmDecl d h a)
-> Functor (GenCmmDecl d h)
forall a b. a -> GenCmmDecl d h b -> GenCmmDecl d h a
forall a b. (a -> b) -> GenCmmDecl d h a -> GenCmmDecl d h b
forall d h a b. a -> GenCmmDecl d h b -> GenCmmDecl d h a
forall d h a b. (a -> b) -> GenCmmDecl d h a -> GenCmmDecl d h b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> GenCmmDecl d h b -> GenCmmDecl d h a
$c<$ :: forall d h a b. a -> GenCmmDecl d h b -> GenCmmDecl d h a
fmap :: forall a b. (a -> b) -> GenCmmDecl d h a -> GenCmmDecl d h b
$cfmap :: forall d h a b. (a -> b) -> GenCmmDecl d h a -> GenCmmDecl d h b
Functor)
type CmmDecl = GenCmmDecl CmmStatics CmmTopInfo CmmGraph
type CmmDeclSRTs = GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph
type RawCmmDecl
= GenCmmDecl
RawCmmStatics
(LabelMap RawCmmStatics)
CmmGraph
type CmmGraph = GenCmmGraph CmmNode
data GenCmmGraph n = CmmGraph { forall (n :: Extensibility -> Extensibility -> *).
GenCmmGraph n -> BlockId
g_entry :: BlockId, forall (n :: Extensibility -> Extensibility -> *).
GenCmmGraph n -> Graph n C C
g_graph :: Graph n C C }
type CmmBlock = Block CmmNode C C
data CmmTopInfo = TopInfo { CmmTopInfo -> LabelMap CmmInfoTable
info_tbls :: LabelMap CmmInfoTable
, CmmTopInfo -> CmmStackInfo
stack_info :: CmmStackInfo }
topInfoTable :: GenCmmDecl a CmmTopInfo (GenCmmGraph n) -> Maybe CmmInfoTable
topInfoTable :: forall a (n :: Extensibility -> Extensibility -> *).
GenCmmDecl a CmmTopInfo (GenCmmGraph n) -> Maybe CmmInfoTable
topInfoTable (CmmProc CmmTopInfo
infos CLabel
_ [GlobalReg]
_ GenCmmGraph n
g) = KeyOf LabelMap -> LabelMap CmmInfoTable -> Maybe CmmInfoTable
forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup (GenCmmGraph n -> BlockId
forall (n :: Extensibility -> Extensibility -> *).
GenCmmGraph n -> BlockId
g_entry GenCmmGraph n
g) (CmmTopInfo -> LabelMap CmmInfoTable
info_tbls CmmTopInfo
infos)
topInfoTable GenCmmDecl a CmmTopInfo (GenCmmGraph n)
_ = Maybe CmmInfoTable
forall a. Maybe a
Nothing
data CmmStackInfo
= StackInfo {
CmmStackInfo -> ByteOff
arg_space :: ByteOff,
CmmStackInfo -> Bool
do_layout :: Bool
}
data CmmInfoTable
= CmmInfoTable {
CmmInfoTable -> CLabel
cit_lbl :: CLabel,
CmmInfoTable -> SMRep
cit_rep :: SMRep,
CmmInfoTable -> ProfilingInfo
cit_prof :: ProfilingInfo,
CmmInfoTable -> Maybe CLabel
cit_srt :: Maybe CLabel,
CmmInfoTable -> Maybe (Id, CostCentreStack)
cit_clo :: Maybe (Id, CostCentreStack)
}
data ProfilingInfo
= NoProfilingInfo
| ProfilingInfo ByteString ByteString
data SectionType
= Text
| Data
| ReadOnlyData
| RelocatableReadOnlyData
| UninitialisedData
| ReadOnlyData16
| CString
| OtherSection String
deriving (ByteOff -> SectionType -> ShowS
[SectionType] -> ShowS
SectionType -> String
(ByteOff -> SectionType -> ShowS)
-> (SectionType -> String)
-> ([SectionType] -> ShowS)
-> Show SectionType
forall a.
(ByteOff -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SectionType] -> ShowS
$cshowList :: [SectionType] -> ShowS
show :: SectionType -> String
$cshow :: SectionType -> String
showsPrec :: ByteOff -> SectionType -> ShowS
$cshowsPrec :: ByteOff -> SectionType -> ShowS
Show)
data SectionProtection
= ReadWriteSection
| ReadOnlySection
| WriteProtectedSection
deriving (SectionProtection -> SectionProtection -> Bool
(SectionProtection -> SectionProtection -> Bool)
-> (SectionProtection -> SectionProtection -> Bool)
-> Eq SectionProtection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SectionProtection -> SectionProtection -> Bool
$c/= :: SectionProtection -> SectionProtection -> Bool
== :: SectionProtection -> SectionProtection -> Bool
$c== :: SectionProtection -> SectionProtection -> Bool
Eq)
sectionProtection :: Section -> SectionProtection
sectionProtection :: Section -> SectionProtection
sectionProtection (Section SectionType
t CLabel
_) = case SectionType
t of
SectionType
Text -> SectionProtection
ReadOnlySection
SectionType
ReadOnlyData -> SectionProtection
ReadOnlySection
SectionType
RelocatableReadOnlyData -> SectionProtection
WriteProtectedSection
SectionType
ReadOnlyData16 -> SectionProtection
ReadOnlySection
SectionType
CString -> SectionProtection
ReadOnlySection
SectionType
Data -> SectionProtection
ReadWriteSection
SectionType
UninitialisedData -> SectionProtection
ReadWriteSection
(OtherSection String
_) -> SectionProtection
ReadWriteSection
data Section = Section SectionType CLabel
data CmmStatic
= CmmStaticLit CmmLit
| CmmUninitialised Int
| CmmString ByteString
| CmmFileEmbed FilePath
instance Outputable CmmStatic where
ppr :: CmmStatic -> SDoc
ppr (CmmStaticLit CmmLit
lit) = String -> SDoc
text String
"CmmStaticLit" SDoc -> SDoc -> SDoc
<+> CmmLit -> SDoc
forall a. Outputable a => a -> SDoc
ppr CmmLit
lit
ppr (CmmUninitialised ByteOff
n) = String -> SDoc
text String
"CmmUninitialised" SDoc -> SDoc -> SDoc
<+> ByteOff -> SDoc
forall a. Outputable a => a -> SDoc
ppr ByteOff
n
ppr (CmmString ByteString
_) = String -> SDoc
text String
"CmmString"
ppr (CmmFileEmbed String
fp) = String -> SDoc
text String
"CmmFileEmbed" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
fp
data GenCmmStatics (rawOnly :: Bool) where
CmmStatics
:: CLabel
-> CmmInfoTable
-> CostCentreStack
-> [CmmLit]
-> GenCmmStatics 'False
CmmStaticsRaw
:: CLabel
-> [CmmStatic]
-> GenCmmStatics a
type CmmStatics = GenCmmStatics 'False
type RawCmmStatics = GenCmmStatics 'True
data GenBasicBlock i
= BasicBlock BlockId [i]
deriving ((forall a b. (a -> b) -> GenBasicBlock a -> GenBasicBlock b)
-> (forall a b. a -> GenBasicBlock b -> GenBasicBlock a)
-> Functor GenBasicBlock
forall a b. a -> GenBasicBlock b -> GenBasicBlock a
forall a b. (a -> b) -> GenBasicBlock a -> GenBasicBlock b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> GenBasicBlock b -> GenBasicBlock a
$c<$ :: forall a b. a -> GenBasicBlock b -> GenBasicBlock a
fmap :: forall a b. (a -> b) -> GenBasicBlock a -> GenBasicBlock b
$cfmap :: forall a b. (a -> b) -> GenBasicBlock a -> GenBasicBlock b
Functor)
blockId :: GenBasicBlock i -> BlockId
blockId :: forall i. GenBasicBlock i -> BlockId
blockId (BasicBlock BlockId
blk_id [i]
_ ) = BlockId
blk_id
newtype ListGraph i
= ListGraph [GenBasicBlock i]
deriving ((forall a b. (a -> b) -> ListGraph a -> ListGraph b)
-> (forall a b. a -> ListGraph b -> ListGraph a)
-> Functor ListGraph
forall a b. a -> ListGraph b -> ListGraph a
forall a b. (a -> b) -> ListGraph a -> ListGraph b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> ListGraph b -> ListGraph a
$c<$ :: forall a b. a -> ListGraph b -> ListGraph a
fmap :: forall a b. (a -> b) -> ListGraph a -> ListGraph b
$cfmap :: forall a b. (a -> b) -> ListGraph a -> ListGraph b
Functor)
instance Outputable instr => Outputable (ListGraph instr) where
ppr :: ListGraph instr -> SDoc
ppr (ListGraph [GenBasicBlock instr]
blocks) = [SDoc] -> SDoc
vcat ((GenBasicBlock instr -> SDoc) -> [GenBasicBlock instr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map GenBasicBlock instr -> SDoc
forall a. Outputable a => a -> SDoc
ppr [GenBasicBlock instr]
blocks)
instance OutputableP env instr => OutputableP env (ListGraph instr) where
pdoc :: env -> ListGraph instr -> SDoc
pdoc env
env ListGraph instr
g = ListGraph SDoc -> SDoc
forall a. Outputable a => a -> SDoc
ppr ((instr -> SDoc) -> ListGraph instr -> ListGraph SDoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (env -> instr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env) ListGraph instr
g)
instance Outputable instr => Outputable (GenBasicBlock instr) where
ppr :: GenBasicBlock instr -> SDoc
ppr = GenBasicBlock instr -> SDoc
forall instr. Outputable instr => GenBasicBlock instr -> SDoc
pprBBlock
instance OutputableP env instr => OutputableP env (GenBasicBlock instr) where
pdoc :: env -> GenBasicBlock instr -> SDoc
pdoc env
env GenBasicBlock instr
block = GenBasicBlock SDoc -> SDoc
forall a. Outputable a => a -> SDoc
ppr ((instr -> SDoc) -> GenBasicBlock instr -> GenBasicBlock SDoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (env -> instr -> SDoc
forall env a. OutputableP env a => env -> a -> SDoc
pdoc env
env) GenBasicBlock instr
block)
pprBBlock :: Outputable stmt => GenBasicBlock stmt -> SDoc
pprBBlock :: forall instr. Outputable instr => GenBasicBlock instr -> SDoc
pprBBlock (BasicBlock BlockId
ident [stmt]
stmts) =
SDoc -> ByteOff -> SDoc -> SDoc
hang (BlockId -> SDoc
forall a. Outputable a => a -> SDoc
ppr BlockId
ident SDoc -> SDoc -> SDoc
<> SDoc
colon) ByteOff
4 ([SDoc] -> SDoc
vcat ((stmt -> SDoc) -> [stmt] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map stmt -> SDoc
forall a. Outputable a => a -> SDoc
ppr [stmt]
stmts))