| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Cmm
Synopsis
- type CmmProgram = [CmmGroup]
 - type CmmGroup = GenCmmGroup CmmStatics CmmTopInfo CmmGraph
 - type CmmGroupSRTs = GenCmmGroup RawCmmStatics CmmTopInfo CmmGraph
 - type RawCmmGroup = GenCmmGroup RawCmmStatics (LabelMap RawCmmStatics) CmmGraph
 - type GenCmmGroup d h g = [GenCmmDecl d h g]
 - type CmmDecl = GenCmmDecl CmmStatics CmmTopInfo CmmGraph
 - type CmmDeclSRTs = GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph
 - data GenCmmDecl d h g
 - type CmmDataDecl = GenCmmDataDecl CmmStatics
 - cmmDataDeclCmmDecl :: GenCmmDataDecl d -> GenCmmDecl d h g
 - type CmmGraph = GenCmmGraph CmmNode
 - data GenCmmGraph (n :: Extensibility -> Extensibility -> Type) = CmmGraph {}
 - toBlockMap :: CmmGraph -> LabelMap CmmBlock
 - revPostorder :: CmmGraph -> [CmmBlock]
 - toBlockList :: CmmGraph -> [CmmBlock]
 - type CmmBlock = Block CmmNode C C
 - type RawCmmDecl = GenCmmDecl RawCmmStatics (LabelMap RawCmmStatics) CmmGraph
 - data Section = Section SectionType CLabel
 - data SectionType
 - data GenCmmStatics (rawOnly :: Bool) where
- CmmStatics :: CLabel -> CmmInfoTable -> CostCentreStack -> [CmmLit] -> [CmmLit] -> GenCmmStatics 'False
 - CmmStaticsRaw :: forall (rawOnly :: Bool). CLabel -> [CmmStatic] -> GenCmmStatics rawOnly
 
 - type CmmStatics = GenCmmStatics 'False
 - type RawCmmStatics = GenCmmStatics 'True
 - data CmmStatic
 - data SectionProtection
 - sectionProtection :: Section -> SectionProtection
 - data GenBasicBlock i = BasicBlock BlockId [i]
 - blockId :: GenBasicBlock i -> BlockId
 - newtype ListGraph i = ListGraph [GenBasicBlock i]
 - pprBBlock :: Outputable stmt => GenBasicBlock stmt -> SDoc
 - data CmmTopInfo = TopInfo {}
 - data CmmStackInfo = StackInfo {}
 - data CmmInfoTable = CmmInfoTable {}
 - topInfoTable :: forall a (n :: Extensibility -> Extensibility -> Type). GenCmmDecl a CmmTopInfo (GenCmmGraph n) -> Maybe CmmInfoTable
 - data ClosureTypeInfo
- = Constr ConTagZ ConstrDescription
 - | Fun FunArity ArgDescr
 - | Thunk
 - | ThunkSelector SelectorOffset
 - | BlackHole
 - | IndStatic
 
 - data ProfilingInfo
 - type ConstrDescription = ByteString
 - module GHC.Cmm.Node
 - module GHC.Cmm.Expr
 - pprCmmGroup :: (OutputableP Platform d, OutputableP Platform info, OutputableP Platform g) => Platform -> GenCmmGroup d info g -> SDoc
 - pprSection :: Platform -> Section -> SDoc
 - pprStatic :: Platform -> CmmStatic -> SDoc
 
Cmm top-level datatypes
type CmmProgram = [CmmGroup] Source #
type CmmGroup = GenCmmGroup CmmStatics CmmTopInfo CmmGraph Source #
Cmm group before SRT generation
type CmmGroupSRTs = GenCmmGroup RawCmmStatics CmmTopInfo CmmGraph Source #
Cmm group with SRTs
type RawCmmGroup = GenCmmGroup RawCmmStatics (LabelMap RawCmmStatics) CmmGraph Source #
Raw cmm group (TODO (osa): not sure what that means)
type GenCmmGroup d h g = [GenCmmDecl d h g] Source #
type CmmDecl = GenCmmDecl CmmStatics CmmTopInfo CmmGraph Source #
data GenCmmDecl d h g Source #
A top-level chunk, abstracted over the type of the contents of the basic blocks (Cmm or instructions are the likely instantiations).
Instances
| (OutputableP Platform d, OutputableP Platform info, OutputableP Platform i) => OutputableP Platform (GenCmmDecl d info i) Source # | |
| Functor (GenCmmDecl d h) Source # | |
Defined in GHC.Cmm Methods fmap :: (a -> b) -> GenCmmDecl d h a -> GenCmmDecl d h b Source # (<$) :: a -> GenCmmDecl d h b -> GenCmmDecl d h a Source #  | |
type CmmDataDecl = GenCmmDataDecl CmmStatics Source #
cmmDataDeclCmmDecl :: GenCmmDataDecl d -> GenCmmDecl d h g Source #
type CmmGraph = GenCmmGraph CmmNode Source #
data GenCmmGraph (n :: Extensibility -> Extensibility -> Type) Source #
revPostorder :: CmmGraph -> [CmmBlock] Source #
toBlockList :: CmmGraph -> [CmmBlock] Source #
data SectionType Source #
data GenCmmStatics (rawOnly :: Bool) where Source #
Constructors
| CmmStatics :: CLabel -> CmmInfoTable -> CostCentreStack -> [CmmLit] -> [CmmLit] -> GenCmmStatics 'False | |
| CmmStaticsRaw :: forall (rawOnly :: Bool). CLabel -> [CmmStatic] -> GenCmmStatics rawOnly | Static data, after SRTs are generated  | 
Instances
type CmmStatics = GenCmmStatics 'False Source #
type RawCmmStatics = GenCmmStatics 'True Source #
Constructors
| CmmStaticLit CmmLit | a literal value, size given by cmmLitRep of the literal.  | 
| CmmUninitialised Int | uninitialised data, N bytes long  | 
| CmmString ByteString | string of 8-bit values only, not zero terminated.  | 
| CmmFileEmbed FilePath Int | an embedded binary file and its byte length  | 
data SectionProtection Source #
Constructors
| ReadWriteSection | |
| ReadOnlySection | |
| WriteProtectedSection | 
Instances
| Eq SectionProtection Source # | |
Defined in GHC.Cmm Methods (==) :: SectionProtection -> SectionProtection -> Bool # (/=) :: SectionProtection -> SectionProtection -> Bool #  | |
sectionProtection :: Section -> SectionProtection Source #
Should a data in this section be considered constant at runtime
Blocks containing lists
data GenBasicBlock i Source #
Constructors
| BasicBlock BlockId [i] | 
Instances
| Functor GenBasicBlock Source # | |
Defined in GHC.Cmm Methods fmap :: (a -> b) -> GenBasicBlock a -> GenBasicBlock b Source # (<$) :: a -> GenBasicBlock b -> GenBasicBlock a Source #  | |
| OutputableP env instr => OutputableP env (GenBasicBlock instr) Source # | |
| Outputable instr => Outputable (GenBasicBlock instr) Source # | |
blockId :: GenBasicBlock i -> BlockId Source #
The branch block id is that of the first block in the branch, which is that branch's entry point
Constructors
| ListGraph [GenBasicBlock i] | 
Instances
| Functor ListGraph Source # | |
| OutputableP env instr => OutputableP env (ListGraph instr) Source # | |
| Outputable instr => Outputable (ListGraph instr) Source # | |
pprBBlock :: Outputable stmt => GenBasicBlock stmt -> SDoc Source #
Info Tables
data CmmTopInfo Source #
CmmTopInfo is attached to each CmmDecl (see defn of CmmGroup), and contains the extra info (beyond the executable code) that belongs to that CmmDecl.
Constructors
| TopInfo | |
Fields  | |
Instances
data CmmStackInfo Source #
Instances
data CmmInfoTable Source #
Info table as a haskell data type
Constructors
| CmmInfoTable | |
Instances
| Eq CmmInfoTable Source # | |
Defined in GHC.Cmm  | |
| OutputableP Platform CmmInfoTable Source # | |
topInfoTable :: forall a (n :: Extensibility -> Extensibility -> Type). GenCmmDecl a CmmTopInfo (GenCmmGraph n) -> Maybe CmmInfoTable Source #
data ClosureTypeInfo Source #
Constructors
| Constr ConTagZ ConstrDescription | |
| Fun FunArity ArgDescr | |
| Thunk | |
| ThunkSelector SelectorOffset | |
| BlackHole | |
| IndStatic | 
Instances
| Outputable ClosureTypeInfo Source # | |
Defined in GHC.Runtime.Heap.Layout Methods ppr :: ClosureTypeInfo -> SDoc Source #  | |
| Eq ClosureTypeInfo Source # | |
Defined in GHC.Runtime.Heap.Layout Methods (==) :: ClosureTypeInfo -> ClosureTypeInfo -> Bool # (/=) :: ClosureTypeInfo -> ClosureTypeInfo -> Bool #  | |
data ProfilingInfo Source #
Constructors
| NoProfilingInfo | |
| ProfilingInfo ByteString ByteString | 
Instances
| Eq ProfilingInfo Source # | |
Defined in GHC.Cmm Methods (==) :: ProfilingInfo -> ProfilingInfo -> Bool # (/=) :: ProfilingInfo -> ProfilingInfo -> Bool #  | |
type ConstrDescription = ByteString Source #
Statements, expressions and types
module GHC.Cmm.Node
module GHC.Cmm.Expr
Pretty-printing
pprCmmGroup :: (OutputableP Platform d, OutputableP Platform info, OutputableP Platform g) => Platform -> GenCmmGroup d info g -> SDoc Source #