Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data CmmNode e x where
- CmmEntry :: !Label -> CmmTickScope -> CmmNode C O
- CmmComment :: FastString -> CmmNode O O
- CmmTick :: !CmmTickish -> CmmNode O O
- CmmUnwind :: [(GlobalReg, Maybe CmmExpr)] -> CmmNode O O
- CmmAssign :: !CmmReg -> !CmmExpr -> CmmNode O O
- CmmStore :: !CmmExpr -> !CmmExpr -> CmmNode O O
- CmmUnsafeForeignCall :: ForeignTarget -> [CmmFormal] -> [CmmActual] -> CmmNode O O
- CmmBranch :: !Label -> CmmNode O C
- CmmCondBranch :: {..} -> CmmNode O C
- CmmSwitch :: CmmExpr -> SwitchTargets -> CmmNode O C
- CmmCall :: {..} -> CmmNode O C
- CmmForeignCall :: {..} -> CmmNode O C
- type CmmFormal = LocalReg
- type CmmActual = CmmExpr
- type CmmTickish = Tickish ()
- type UpdFrameOffset = ByteOff
- data Convention
- data ForeignConvention = ForeignConvention CCallConv [ForeignHint] [ForeignHint] CmmReturnInfo
- data ForeignTarget
- foreignTargetHints :: ForeignTarget -> ([ForeignHint], [ForeignHint])
- data CmmReturnInfo
- mapExp :: (CmmExpr -> CmmExpr) -> CmmNode e x -> CmmNode e x
- mapExpDeep :: (CmmExpr -> CmmExpr) -> CmmNode e x -> CmmNode e x
- wrapRecExp :: (CmmExpr -> CmmExpr) -> CmmExpr -> CmmExpr
- foldExp :: (CmmExpr -> z -> z) -> CmmNode e x -> z -> z
- foldExpDeep :: (CmmExpr -> z -> z) -> CmmNode e x -> z -> z
- wrapRecExpf :: (CmmExpr -> z -> z) -> CmmExpr -> z -> z
- mapExpM :: (CmmExpr -> Maybe CmmExpr) -> CmmNode e x -> Maybe (CmmNode e x)
- mapExpDeepM :: (CmmExpr -> Maybe CmmExpr) -> CmmNode e x -> Maybe (CmmNode e x)
- wrapRecExpM :: (CmmExpr -> Maybe CmmExpr) -> CmmExpr -> Maybe CmmExpr
- mapSuccessors :: (Label -> Label) -> CmmNode O C -> CmmNode O C
- data CmmTickScope
- isTickSubScope :: CmmTickScope -> CmmTickScope -> Bool
- combineTickScopes :: CmmTickScope -> CmmTickScope -> CmmTickScope
Documentation
data CmmNode e x where Source #
CmmEntry :: !Label -> CmmTickScope -> CmmNode C O | |
CmmComment :: FastString -> CmmNode O O | |
CmmTick :: !CmmTickish -> CmmNode O O | |
CmmUnwind :: [(GlobalReg, Maybe CmmExpr)] -> CmmNode O O | |
CmmAssign :: !CmmReg -> !CmmExpr -> CmmNode O O | |
CmmStore :: !CmmExpr -> !CmmExpr -> CmmNode O O | |
CmmUnsafeForeignCall :: ForeignTarget -> [CmmFormal] -> [CmmActual] -> CmmNode O O | |
CmmBranch :: !Label -> CmmNode O C | |
CmmCondBranch | |
CmmSwitch :: CmmExpr -> SwitchTargets -> CmmNode O C | |
CmmCall | |
| |
CmmForeignCall | |
Instances
Outputable CmmGraph # | |
NonLocal CmmNode # | |
DefinerOfRegs GlobalReg (CmmNode e x) # | |
DefinerOfRegs LocalReg (CmmNode e x) # | |
UserOfRegs GlobalReg (CmmNode e x) # | |
UserOfRegs LocalReg (CmmNode e x) # | |
Eq (CmmNode e x) # | |
Outputable (CmmNode e x) # | |
Outputable (Block CmmNode C C) # | |
Outputable (Block CmmNode C O) # | |
Outputable (Block CmmNode O C) # | |
Outputable (Block CmmNode O O) # | |
Outputable (Graph CmmNode e x) # | |
type CmmTickish = Tickish () Source #
Tickish in Cmm context (annotations only)
type UpdFrameOffset = ByteOff Source #
data Convention Source #
A convention maps a list of values (function arguments or return values) to registers or stack locations.
NativeDirectCall | top-level Haskell functions use |
NativeNodeCall | non-top-level Haskell functions, which pass the address of the function closure in R1 (regardless of whether R1 is a real register or not), and the rest of the arguments in registers or on the stack. |
NativeReturn | a native return. The convention for returns depends on how many values are returned: for just one value returned, the appropriate register is used (R1, F1, etc.). regardless of whether it is a real register or not. For multiple values returned, they are mapped to registers or the stack. |
Slow | Slow entry points: all args pushed on the stack |
GC | Entry to the garbage collector: uses the node reg! (TODO: I don't think we need this --SDM) |
Instances
Eq Convention # | |
Defined in CmmNode (==) :: Convention -> Convention -> Bool # (/=) :: Convention -> Convention -> Bool # | |
Outputable Convention # | |
data ForeignConvention Source #
Instances
Eq ForeignConvention # | |
Defined in CmmNode (==) :: ForeignConvention -> ForeignConvention -> Bool # (/=) :: ForeignConvention -> ForeignConvention -> Bool # | |
Outputable ForeignConvention # | |
data ForeignTarget Source #
Instances
Eq ForeignTarget # | |
Defined in CmmNode (==) :: ForeignTarget -> ForeignTarget -> Bool # (/=) :: ForeignTarget -> ForeignTarget -> Bool # | |
Outputable ForeignTarget # | |
(Ord r, UserOfRegs r CmmReg) => UserOfRegs r ForeignTarget # | |
Defined in CmmNode foldRegsUsed :: DynFlags -> (b -> r -> b) -> b -> ForeignTarget -> b Source # |
foreignTargetHints :: ForeignTarget -> ([ForeignHint], [ForeignHint]) Source #
data CmmReturnInfo Source #
Instances
Eq CmmReturnInfo # | |
Defined in CmmNode (==) :: CmmReturnInfo -> CmmReturnInfo -> Bool # (/=) :: CmmReturnInfo -> CmmReturnInfo -> Bool # | |
Outputable CmmReturnInfo # | |
foldExpDeep :: (CmmExpr -> z -> z) -> CmmNode e x -> z -> z Source #
wrapRecExpf :: (CmmExpr -> z -> z) -> CmmExpr -> z -> z Source #
Tick scopes
data CmmTickScope Source #
Tick scope identifier, allowing us to reason about what annotations in a Cmm block should scope over. We especially take care to allow optimisations to reorganise blocks without losing tick association in the process.
GlobalScope | The global scope is the "root" of the scope graph. Every scope is a sub-scope of the global scope. It doesn't make sense to add ticks to this scope. On the other hand, this means that setting this scope on a block means no ticks apply to it. |
SubScope !Unique CmmTickScope | Constructs a new sub-scope to an existing scope. This allows
us to translate Core-style scoping rules (see tick1 case ... of A -> tick2 ... B -> tick3 ... We want the top-level tick annotation to apply to blocks generated for the A and B alternatives. We can achieve that by generating tick1 into a block with scope a, while the code for alternatives A and B gets generated into sub-scopes a/b and a/c respectively. |
CombinedScope CmmTickScope CmmTickScope | A combined scope scopes over everything that the two given scopes cover. It is therefore a sub-scope of either scope. This is required for optimisations. Consider common block elimination: A -> tick2 case ... of C -> [common] B -> tick3 case ... of D -> [common] We will generate code for the C and D alternatives, and figure out afterwards that it's actually common code. Scoping rules dictate that the resulting common block needs to be covered by both tick2 and tick3, therefore we need to construct a scope that is a child to *both* scope. Now we can do that - if we assign the scopes ac and bd to the common-ed up blocks, the new block could have a combined tick scope ac+bd, which both tick2 and tick3 apply to. |
Instances
Eq CmmTickScope # | |
Defined in CmmNode (==) :: CmmTickScope -> CmmTickScope -> Bool # (/=) :: CmmTickScope -> CmmTickScope -> Bool # | |
Ord CmmTickScope # | |
Defined in CmmNode compare :: CmmTickScope -> CmmTickScope -> Ordering # (<) :: CmmTickScope -> CmmTickScope -> Bool # (<=) :: CmmTickScope -> CmmTickScope -> Bool # (>) :: CmmTickScope -> CmmTickScope -> Bool # (>=) :: CmmTickScope -> CmmTickScope -> Bool # max :: CmmTickScope -> CmmTickScope -> CmmTickScope # min :: CmmTickScope -> CmmTickScope -> CmmTickScope # | |
Outputable CmmTickScope # | |
isTickSubScope :: CmmTickScope -> CmmTickScope -> Bool Source #
Checks whether two tick scopes are sub-scopes of each other. True if the two scopes are equal.
combineTickScopes :: CmmTickScope -> CmmTickScope -> CmmTickScope Source #
Combine two tick scopes. The new scope should be sub-scope of both parameters. We simplfy automatically if one tick scope is a sub-scope of the other already.