ghc-6.12.1: The GHC APISource codeContentsIndex
ZipCfgCmmRep
Documentation
type CmmZ = GenCmm CmmStatic CmmInfo (CmmStackInfo, CmmGraph)Source
type CmmTopZ = GenCmmTop CmmStatic CmmInfo (CmmStackInfo, CmmGraph)Source
type CmmGraph = LGraph Middle LastSource
type CmmBlock = Block Middle LastSource
type CmmAGraph = AGraph Middle LastSource
data Middle Source
Constructors
MidComment FastString
MidAssign CmmReg CmmExpr
MidStore CmmExpr CmmExpr
MidForeignCall ForeignSafety MidCallTarget CmmFormals CmmActuals
show/hide Instances
data Last Source
Constructors
LastBranch BlockId
LastCondBranch
cml_pred :: CmmExpr
cml_true :: BlockId
cml_false :: BlockId
LastSwitch CmmExpr [Maybe BlockId]
LastCall
cml_target :: CmmExpr
cml_cont :: Maybe BlockId
cml_args :: ByteOff
cml_ret_args :: ByteOff
cml_ret_off :: Maybe ByteOff
show/hide Instances
data MidCallTarget Source
Constructors
ForeignTarget CmmExpr ForeignConvention
PrimTarget CallishMachOp
show/hide Instances
type UpdFrameOffset = ByteOffSource
data Convention Source
Constructors
NativeDirectCall
NativeNodeCall
NativeReturn
Slow
GC
PrimOpCall
PrimOpReturn
Foreign ForeignConvention
Private
show/hide Instances
data ForeignConvention Source
Constructors
ForeignConvention CCallConv [ForeignHint] [ForeignHint]
show/hide Instances
data ForeignSafety Source
Constructors
Unsafe
Safe BlockId UpdFrameOffset
show/hide Instances
data ValueDirection Source
Constructors
Arguments
Results
show/hide Instances
data ForeignHint Source
Constructors
NoHint
AddrHint
SignedHint
show/hide Instances
type CmmBackwardFixedPoint a = BackwardFixedPoint Middle Last a ()Source
type CmmForwardFixedPoint a = ForwardFixedPoint Middle Last a ()Source
pprHinted :: Outputable a => CmmHinted a -> SDocSource
insertBetween :: MonadUnique m => CmmBlock -> [Middle] -> BlockId -> m (CmmBlock, [CmmBlock])Source
mapExpMiddle :: (CmmExpr -> CmmExpr) -> Middle -> MiddleSource
mapExpLast :: (CmmExpr -> CmmExpr) -> Last -> LastSource
mapExpDeepMiddle :: (CmmExpr -> CmmExpr) -> Middle -> MiddleSource
mapExpDeepLast :: (CmmExpr -> CmmExpr) -> Last -> LastSource
foldExpMiddle :: (CmmExpr -> z -> z) -> Middle -> z -> zSource
foldExpLast :: (CmmExpr -> z -> z) -> Last -> z -> zSource
foldExpDeepMiddle :: (CmmExpr -> z -> z) -> Middle -> z -> zSource
foldExpDeepLast :: (CmmExpr -> z -> z) -> Last -> z -> zSource
joinOuts :: DataflowLattice a -> (BlockId -> a) -> Last -> aSource
Produced by Haddock version 2.6.0