Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- type DCmmGroup = GenCmmGroup CmmStatics DCmmTopInfo DCmmGraph
- 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 DCmmDecl = GenCmmDecl CmmStatics DCmmTopInfo DCmmGraph
- type CmmDeclSRTs = GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph
- data GenCmmDecl d h g
- = CmmProc h CLabel [GlobalRegUse] g
- | CmmData Section d
- type CmmDataDecl = GenCmmDataDecl CmmStatics
- cmmDataDeclCmmDecl :: GenCmmDataDecl d -> GenCmmDecl d h g
- type DCmmGraph = GenGenCmmGraph DWrap CmmNode
- type CmmGraph = GenCmmGraph CmmNode
- type GenCmmGraph (n :: Extensibility -> Extensibility -> Type) = GenGenCmmGraph LabelMap n
- data GenGenCmmGraph (s :: Type -> Type) (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
- newtype DWrap a = DWrap [(BlockId, a)]
- unDeterm :: DWrap a -> [(BlockId, a)]
- removeDeterm :: DCmmGroup -> CmmGroup
- removeDetermDecl :: DCmmDecl -> CmmDecl
- removeDetermGraph :: DCmmGraph -> CmmGraph
- data GenBasicBlock i = BasicBlock BlockId [i]
- blockId :: GenBasicBlock i -> BlockId
- newtype ListGraph i = ListGraph [GenBasicBlock i]
- pprBBlock :: Outputable stmt => GenBasicBlock stmt -> SDoc
- data GenCmmTopInfo (f :: Type -> Type) = TopInfo {}
- type DCmmTopInfo = GenCmmTopInfo DWrap
- type CmmTopInfo = GenCmmTopInfo LabelMap
- data CmmStackInfo = StackInfo {}
- data CmmInfoTable = CmmInfoTable {}
- topInfoTable :: forall a (s :: Type -> Type) (n :: Extensibility -> Extensibility -> Type). GenCmmDecl a CmmTopInfo (GenGenCmmGraph s n) -> Maybe CmmInfoTable
- topInfoTableD :: forall a (s :: Type -> Type) (n :: Extensibility -> Extensibility -> Type). GenCmmDecl a DCmmTopInfo (GenGenCmmGraph s 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 DCmmGroup = GenCmmGroup CmmStatics DCmmTopInfo DCmmGraph Source #
Cmm group after STG generation
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).
CmmProc h CLabel [GlobalRegUse] g | |
CmmData Section d |
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 fmap :: (a -> b) -> GenCmmDecl d h a -> GenCmmDecl d h b # (<$) :: a -> GenCmmDecl d h b -> GenCmmDecl d h a # |
type CmmDataDecl = GenCmmDataDecl CmmStatics Source #
cmmDataDeclCmmDecl :: GenCmmDataDecl d -> GenCmmDecl d h g Source #
type CmmGraph = GenCmmGraph CmmNode Source #
type GenCmmGraph (n :: Extensibility -> Extensibility -> Type) = GenGenCmmGraph LabelMap n Source #
data GenGenCmmGraph (s :: Type -> Type) (n :: Extensibility -> Extensibility -> Type) Source #
revPostorder :: CmmGraph -> [CmmBlock] Source #
toBlockList :: CmmGraph -> [CmmBlock] Source #
data SectionType Source #
Text | |
Data | |
ReadOnlyData | |
RelocatableReadOnlyData | |
UninitialisedData | |
InitArray | |
FiniArray | |
CString | |
OtherSection String |
Instances
Show SectionType Source # | |
Defined in GHC.Cmm showsPrec :: Int -> SectionType -> ShowS # show :: SectionType -> String # showList :: [SectionType] -> ShowS # |
data GenCmmStatics (rawOnly :: Bool) where Source #
Static data before or after SRT generation
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 #
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 #
Instances
Eq SectionProtection Source # | |
Defined in GHC.Cmm (==) :: SectionProtection -> SectionProtection -> Bool # (/=) :: SectionProtection -> SectionProtection -> Bool # |
sectionProtection :: Section -> SectionProtection Source #
Should a data in this section be considered constant at runtime
removeDeterm :: DCmmGroup -> CmmGroup Source #
removeDetermDecl :: DCmmDecl -> CmmDecl Source #
Blocks containing lists
data GenBasicBlock i Source #
BasicBlock BlockId [i] |
Instances
Functor GenBasicBlock Source # | |
Defined in GHC.Cmm fmap :: (a -> b) -> GenBasicBlock a -> GenBasicBlock b # (<$) :: a -> GenBasicBlock b -> GenBasicBlock a # | |
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
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 GenCmmTopInfo (f :: Type -> Type) 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.
Instances
type DCmmTopInfo = GenCmmTopInfo DWrap Source #
type CmmTopInfo = GenCmmTopInfo LabelMap Source #
data CmmStackInfo Source #
Instances
data CmmInfoTable Source #
Info table as a haskell data type
Instances
Eq CmmInfoTable Source # | |
Defined in GHC.Cmm (==) :: CmmInfoTable -> CmmInfoTable -> Bool # (/=) :: CmmInfoTable -> CmmInfoTable -> Bool # | |
Ord CmmInfoTable Source # | |
Defined in GHC.Cmm compare :: CmmInfoTable -> CmmInfoTable -> Ordering # (<) :: CmmInfoTable -> CmmInfoTable -> Bool # (<=) :: CmmInfoTable -> CmmInfoTable -> Bool # (>) :: CmmInfoTable -> CmmInfoTable -> Bool # (>=) :: CmmInfoTable -> CmmInfoTable -> Bool # max :: CmmInfoTable -> CmmInfoTable -> CmmInfoTable # min :: CmmInfoTable -> CmmInfoTable -> CmmInfoTable # | |
OutputableP Platform CmmInfoTable Source # | |
topInfoTable :: forall a (s :: Type -> Type) (n :: Extensibility -> Extensibility -> Type). GenCmmDecl a CmmTopInfo (GenGenCmmGraph s n) -> Maybe CmmInfoTable Source #
topInfoTableD :: forall a (s :: Type -> Type) (n :: Extensibility -> Extensibility -> Type). GenCmmDecl a DCmmTopInfo (GenGenCmmGraph s n) -> Maybe CmmInfoTable Source #
data ClosureTypeInfo Source #
Constr ConTagZ ConstrDescription | |
Fun FunArity ArgDescr | |
Thunk | |
ThunkSelector SelectorOffset | |
BlackHole | |
IndStatic |
Instances
Outputable ClosureTypeInfo Source # | |
Defined in GHC.Runtime.Heap.Layout ppr :: ClosureTypeInfo -> SDoc Source # | |
Eq ClosureTypeInfo Source # | |
Defined in GHC.Runtime.Heap.Layout (==) :: ClosureTypeInfo -> ClosureTypeInfo -> Bool # (/=) :: ClosureTypeInfo -> ClosureTypeInfo -> Bool # | |
Ord ClosureTypeInfo Source # | |
Defined in GHC.Runtime.Heap.Layout compare :: ClosureTypeInfo -> ClosureTypeInfo -> Ordering # (<) :: ClosureTypeInfo -> ClosureTypeInfo -> Bool # (<=) :: ClosureTypeInfo -> ClosureTypeInfo -> Bool # (>) :: ClosureTypeInfo -> ClosureTypeInfo -> Bool # (>=) :: ClosureTypeInfo -> ClosureTypeInfo -> Bool # max :: ClosureTypeInfo -> ClosureTypeInfo -> ClosureTypeInfo # min :: ClosureTypeInfo -> ClosureTypeInfo -> ClosureTypeInfo # |
data ProfilingInfo Source #
Instances
Eq ProfilingInfo Source # | |
Defined in GHC.Cmm (==) :: ProfilingInfo -> ProfilingInfo -> Bool # (/=) :: ProfilingInfo -> ProfilingInfo -> Bool # | |
Ord ProfilingInfo Source # | |
Defined in GHC.Cmm compare :: ProfilingInfo -> ProfilingInfo -> Ordering # (<) :: ProfilingInfo -> ProfilingInfo -> Bool # (<=) :: ProfilingInfo -> ProfilingInfo -> Bool # (>) :: ProfilingInfo -> ProfilingInfo -> Bool # (>=) :: ProfilingInfo -> ProfilingInfo -> Bool # max :: ProfilingInfo -> ProfilingInfo -> ProfilingInfo # min :: ProfilingInfo -> ProfilingInfo -> ProfilingInfo # |
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 #