Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data DebugBlock = DebugBlock {
- dblProcedure :: !Label
- dblLabel :: !Label
- dblCLabel :: !CLabel
- dblHasInfoTbl :: !Bool
- dblParent :: !(Maybe DebugBlock)
- dblTicks :: ![CmmTickish]
- dblSourceTick :: !(Maybe CmmTickish)
- dblPosition :: !(Maybe Int)
- dblUnwind :: [UnwindPoint]
- dblBlocks :: ![DebugBlock]
- cmmDebugGen :: ModLocation -> RawCmmGroup -> [DebugBlock]
- cmmDebugLabels :: (i -> Bool) -> GenCmmGroup d g (ListGraph i) -> [Label]
- cmmDebugLink :: [Label] -> LabelMap [UnwindPoint] -> [DebugBlock] -> [DebugBlock]
- debugToMap :: [DebugBlock] -> LabelMap DebugBlock
- type UnwindTable = Map GlobalReg (Maybe UnwindExpr)
- data UnwindPoint = UnwindPoint !CLabel !UnwindTable
- data UnwindExpr
- toUnwindExpr :: Platform -> CmmExpr -> UnwindExpr
- pprUnwindTable :: IsLine doc => Platform -> UnwindTable -> doc
Documentation
data DebugBlock Source #
Debug information about a block of code. Ticks scope over nested blocks.
DebugBlock | |
|
Instances
OutputableP Platform DebugBlock Source # | |
Defined in GHC.Cmm.DebugBlock |
cmmDebugGen :: ModLocation -> RawCmmGroup -> [DebugBlock] Source #
Extract debug data from a group of procedures. We will prefer source notes that come from the given module (presumably the module that we are currently compiling).
cmmDebugLabels :: (i -> Bool) -> GenCmmGroup d g (ListGraph i) -> [Label] Source #
cmmDebugLink :: [Label] -> LabelMap [UnwindPoint] -> [DebugBlock] -> [DebugBlock] Source #
Sets position and unwind table fields in the debug block tree according to native generated code.
debugToMap :: [DebugBlock] -> LabelMap DebugBlock Source #
Converts debug blocks into a label map for easier lookups
Unwinding information
type UnwindTable = Map GlobalReg (Maybe UnwindExpr) Source #
Maps registers to expressions that yield their "old" values
further up the stack. Most interesting for the stack pointer Sp
,
but might be useful to document saved registers, too. Note that a
register's value will be Nothing
when the register's previous
value cannot be reconstructed.
data UnwindPoint Source #
A label associated with an UnwindTable
Instances
OutputableP Platform UnwindPoint Source # | |
Defined in GHC.Cmm.DebugBlock |
data UnwindExpr Source #
Expressions, used for unwind information
UwConst !Int | literal value |
UwReg !GlobalReg !Int | register plus offset |
UwDeref UnwindExpr | pointer dereferencing |
UwLabel CLabel | |
UwPlus UnwindExpr UnwindExpr | |
UwMinus UnwindExpr UnwindExpr | |
UwTimes UnwindExpr UnwindExpr |
Instances
Eq UnwindExpr Source # | |
Defined in GHC.Cmm.DebugBlock (==) :: UnwindExpr -> UnwindExpr -> Bool # (/=) :: UnwindExpr -> UnwindExpr -> Bool # | |
OutputableP Platform UnwindExpr Source # | |
Defined in GHC.Cmm.DebugBlock |
toUnwindExpr :: Platform -> CmmExpr -> UnwindExpr Source #
Conversion of Cmm expressions to unwind expressions. We check for unsupported operator usages and simplify the expression as far as possible.
pprUnwindTable :: IsLine doc => Platform -> UnwindTable -> doc Source #