| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Debugger.Monad
Synopsis
- newtype Debugger a = Debugger {}
- data DebuggerState = DebuggerState {}
- data BreakpointStatus
- data RunDebuggerSettings = RunDebuggerSettings {}
- runDebugger :: Handle -> FilePath -> FilePath -> FilePath -> [String] -> [String] -> FilePath -> RunDebuggerSettings -> Debugger a -> IO a
- debuggerLoggerAction :: Handle -> LogAction
- registerBreakpoint :: BreakpointId -> BreakpointStatus -> BreakpointKind -> Debugger Bool
- getActiveBreakpoints :: Maybe FilePath -> Debugger [BreakpointId]
- getAllLoadedModules :: GhcMonad m => m [ModSummary]
- getModuleByPath :: FilePath -> Debugger (Either String ModSummary)
- lookupVarByReference :: Int -> Debugger (Maybe TermKey)
- getVarReference :: TermKey -> Debugger Int
- leaveSuspendedState :: Debugger ()
- defaultDepth :: Int
- seqTerm :: Term -> Debugger Term
- deepseqTerm :: Term -> Debugger Term
- continueToCompletion :: Debugger ExecResult
- breakpointStatusInt :: BreakpointStatus -> Int
- freshInt :: Debugger Int
- initialDebuggerState :: Ghc DebuggerState
- liftGhc :: Ghc a -> Debugger a
- type Warning = String
- displayWarnings :: [Warning] -> Debugger ()
Documentation
A debugger action.
Constructors
| Debugger | |
| Fields | |
Instances
data DebuggerState Source #
State required to run the debugger.
- Keep track of active breakpoints to easily unset them all.
Constructors
| DebuggerState | |
| Fields 
 | |
Instances
| MonadReader DebuggerState Debugger Source # | |
| Defined in GHC.Debugger.Monad Methods ask :: Debugger DebuggerState # local :: (DebuggerState -> DebuggerState) -> Debugger a -> Debugger a # reader :: (DebuggerState -> a) -> Debugger a # | |
data BreakpointStatus Source #
Enabling/Disabling a breakpoint
Constructors
| BreakpointDisabled | Breakpoint is disabled Note: this must be the first constructor s.t.
   | 
| BreakpointEnabled | Breakpoint is enabled | 
| BreakpointAfterCount Int | Breakpoint is disabled the first N times and enabled afterwards | 
Instances
| Eq BreakpointStatus Source # | |
| Defined in GHC.Debugger.Monad Methods (==) :: BreakpointStatus -> BreakpointStatus -> Bool # (/=) :: BreakpointStatus -> BreakpointStatus -> Bool # | |
| Ord BreakpointStatus Source # | |
| Defined in GHC.Debugger.Monad Methods compare :: BreakpointStatus -> BreakpointStatus -> Ordering # (<) :: BreakpointStatus -> BreakpointStatus -> Bool # (<=) :: BreakpointStatus -> BreakpointStatus -> Bool # (>) :: BreakpointStatus -> BreakpointStatus -> Bool # (>=) :: BreakpointStatus -> BreakpointStatus -> Bool # max :: BreakpointStatus -> BreakpointStatus -> BreakpointStatus # min :: BreakpointStatus -> BreakpointStatus -> BreakpointStatus # | |
data RunDebuggerSettings Source #
Additional settings configuring the debugger
Constructors
| RunDebuggerSettings | |
| Fields | |
Arguments
| :: Handle | The handle to which GHC's output is logged. The debuggee output is not affected by this parameter. | 
| -> FilePath | Cradle root directory | 
| -> FilePath | Component root directory | 
| -> FilePath | The libdir (given with -B as an arg) | 
| -> [String] | The list of units included in the invocation | 
| -> [String] | The full ghc invocation (as constructed by hie-bios flags) | 
| -> FilePath | Path to the main function | 
| -> RunDebuggerSettings | Other debugger run settings | 
| -> Debugger a | 
 | 
| -> IO a | 
Run a Debugger action on a session constructed from a given GHC invocation.
debuggerLoggerAction :: Handle -> LogAction Source #
The logger action used to log GHC output
registerBreakpoint :: BreakpointId -> BreakpointStatus -> BreakpointKind -> Debugger Bool Source #
Registers or deletes a breakpoint in the GHC session and from the list of
 active breakpoints that is kept in DebuggerState, depending on the
 BreakpointStatus being set.
Returns True when the breakpoint status is changed.
getActiveBreakpoints :: Maybe FilePath -> Debugger [BreakpointId] Source #
Get a list with all currently active breakpoints on the given module (by path)
If the path argument is Nothing, get all active function breakpoints instead
getAllLoadedModules :: GhcMonad m => m [ModSummary] Source #
List all loaded modules ModSummarys
getModuleByPath :: FilePath -> Debugger (Either String ModSummary) Source #
Get a ModSummary of a loaded module given its FilePath
lookupVarByReference :: Int -> Debugger (Maybe TermKey) Source #
Find a variable's associated Term and Name by reference (Int)
leaveSuspendedState :: Debugger () Source #
Whenever we run a request that continues execution from the current suspended state, such as Next,Step,Continue, this function should be called to delete the variable references that become invalid as we leave the suspended state.
In particular, varReferences
See also section "Lifetime of Objects References" in the DAP specification.
defaultDepth :: Int Source #
seqTerm :: Term -> Debugger Term Source #
Evaluate a suspended Term to WHNF.
Used in getVariables
continueToCompletion :: Debugger ExecResult Source #
Resume execution with single step mode RunToCompletion, skipping all breakpoints we hit, until we reach ExecComplete.
We use this in doEval because we want to ignore breakpoints in expressions given at the prompt.
breakpointStatusInt :: BreakpointStatus -> Int Source #
Turn a BreakpointStatus into its Int representation for BreakArray
initialDebuggerState :: Ghc DebuggerState Source #
Initialize a DebuggerState
displayWarnings :: [Warning] -> Debugger () Source #