ghc-9.15: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.ByteCode.Breakpoints

Description

Breakpoint information constructed during ByteCode generation.

Specifically, code-generation breakpoints are referred to as "internal breakpoints", the internal breakpoint data for a module is stored in InternalModBreaks, and is uniquely identified at runtime by an InternalBreakpointId.

See Note [ModBreaks vs InternalModBreaks] and Note [Breakpoint identifiers]

Synopsis

Internal Mod Breaks

data InternalModBreaks Source #

Internal mod breaks store the runtime-relevant information of breakpoints.

Importantly, it maps InternalBreakpointIds to CgBreakInfo.

InternalModBreaks are constructed during bytecode generation and stored in CompiledByteCode afterwards.

Constructors

InternalModBreaks 

Fields

  • imodBreaks_breakInfo :: !(IntMap CgBreakInfo)

    Access code-gen time information about a breakpoint, indexed by InternalBreakpointId.

  • imodBreaks_modBreaks :: !ModBreaks

    Store the ModBreaks for this module

    Recall Note [Breakpoint identifiers]: for some module A, an *occurrence* of a breakpoint in A may have been inlined from some breakpoint *defined* in module B.

    This ModBreaks contains information regarding all the breakpoints defined in the module this InternalModBreaks corresponds to. It does not necessarily have information regarding all the breakpoint occurrences registered in imodBreaks_breakInfo. Some of those occurrences may refer breakpoints inlined from other modules.

data CgBreakInfo Source #

Information about a breakpoint that we know at code-generation time In order to be used, this needs to be hydrated relative to the current HscEnv by hydrateCgBreakInfo. Everything here can be fully forced and that's critical for preventing space leaks (see #22530)

Constructors

CgBreakInfo 

Fields

  • cgb_tyvars :: ![IfaceTvBndr]

    Type variables in scope at the breakpoint

  • cgb_vars :: ![Maybe (IfaceIdBndr, Word)]
     
  • cgb_resty :: !IfaceType
     
  • cgb_tick_id :: !(Either InternalBreakLoc BreakpointId)

    This field records the original breakpoint tick identifier for this internal breakpoint info. It is used to convert a breakpoint *occurrence* index (InternalBreakpointId) into a *definition* index (BreakpointId).

    The modules of breakpoint occurrence and breakpoint definition are not necessarily the same: See Note [Breakpoint identifiers].

    If there is no original tick identifier (that is, the breakpoint was created during code generation), we re-use the BreakpointId of something else. It would also be reasonable to have an Either something BreakpointId for cgb_tick_id, but currently we can always re-use a source-level BreakpointId. In the case of step-out, see Note [Debugger: Stepout internal break locs]

Instances

Instances details
Outputable CgBreakInfo Source # 
Instance details

Defined in GHC.ByteCode.Breakpoints

Methods

ppr :: CgBreakInfo -> SDoc Source #

mkInternalModBreaks :: Module -> IntMap CgBreakInfo -> ModBreaks -> InternalModBreaks Source #

Construct an InternalModBreaks.

INVARIANT: The given ModBreaks correspond to the same module as this InternalModBreaks module (the first argument) and its breakpoint infos (the IntMap CgBreakInfo argument)

imodBreaks_module :: InternalModBreaks -> Module Source #

Get the module to which these InternalModBreaks correspond

Internal breakpoint identifier

type BreakInfoIndex = Int Source #

Internal breakpoint info index

newtype InternalBreakLoc Source #

Breakpoints created during code generation don't have a source-level tick location. Instead, we re-use an existing one.

Operations

Internal-level operations

Source-level information operations

getBreakLoc :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO SrcSpan Source #

Get the source span for this breakpoint

getBreakVars :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO [OccName] Source #

Get the vars for this breakpoint

getBreakDecls :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO [String] Source #

Get the decls for this breakpoint

getBreakCCS :: (Module -> IO ModBreaks) -> InternalBreakpointId -> InternalModBreaks -> IO (String, String) Source #

Get the decls for this breakpoint

getBreakSourceId :: InternalBreakpointId -> InternalModBreaks -> BreakpointId Source #

Get the source module and tick index for this breakpoint (as opposed to the module where this breakpoint occurs, which is in InternalBreakpointId)

getBreakSourceMod :: InternalBreakpointId -> InternalModBreaks -> Module Source #

Get the source module for this breakpoint (where the breakpoint is defined)

Utils