ghc-debugger
Safe HaskellNone
LanguageHaskell2010

GHC.Debugger.Monad

Synopsis

Documentation

newtype Debugger a Source #

A debugger action.

Constructors

Debugger 

Instances

Instances details
MonadCatch Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

Methods

catch :: (HasCallStack, Exception e) => Debugger a -> (e -> Debugger a) -> Debugger a #

MonadMask Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

Methods

mask :: HasCallStack => ((forall a. Debugger a -> Debugger a) -> Debugger b) -> Debugger b #

uninterruptibleMask :: HasCallStack => ((forall a. Debugger a -> Debugger a) -> Debugger b) -> Debugger b #

generalBracket :: HasCallStack => Debugger a -> (a -> ExitCase b -> Debugger c) -> (a -> Debugger b) -> Debugger (b, c) #

MonadThrow Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

Methods

throwM :: (HasCallStack, Exception e) => e -> Debugger a #

HasDynFlags Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

GhcMonad Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

HasLogger Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

Applicative Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

Methods

pure :: a -> Debugger a #

(<*>) :: Debugger (a -> b) -> Debugger a -> Debugger b #

liftA2 :: (a -> b -> c) -> Debugger a -> Debugger b -> Debugger c #

(*>) :: Debugger a -> Debugger b -> Debugger b #

(<*) :: Debugger a -> Debugger b -> Debugger a #

Functor Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

Methods

fmap :: (a -> b) -> Debugger a -> Debugger b #

(<$) :: a -> Debugger b -> Debugger a #

Monad Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

Methods

(>>=) :: Debugger a -> (a -> Debugger b) -> Debugger b #

(>>) :: Debugger a -> Debugger b -> Debugger b #

return :: a -> Debugger a #

MonadIO Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

Methods

liftIO :: IO a -> Debugger a #

MonadReader DebuggerState Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

data DebuggerState Source #

State required to run the debugger.

  • Keep track of active breakpoints to easily unset them all.

Constructors

DebuggerState 

Fields

Instances

Instances details
MonadReader DebuggerState Debugger Source # 
Instance details

Defined in GHC.Debugger.Monad

data BreakpointStatus Source #

Enabling/Disabling a breakpoint

Constructors

BreakpointDisabled

Breakpoint is disabled

Note: this must be the first constructor s.t. BreakpointDisabled < {BreakpointEnabled, BreakpointAfterCount}

BreakpointEnabled

Breakpoint is enabled

BreakpointAfterCount Int

Breakpoint is disabled the first N times and enabled afterwards

data RunDebuggerSettings Source #

Additional settings configuring the debugger

runDebugger Source #

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

Debugger action to run on the session constructed from this invocation

-> 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

lookupVarByReference :: Int -> Debugger (Maybe TermKey) Source #

Find a variable's associated Term and Name by reference (Int)

getVarReference :: TermKey -> Debugger Int Source #

Finds or creates an integer var reference for the given TermKey. TODO: Arguably, this mapping should be part of the debug-adapter, and ghc-debugger should deal in TermKey terms only.

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 is reset.

See also section "Lifetime of Objects References" in the DAP specification.

seqTerm :: Term -> Debugger Term Source #

Evaluate a suspended Term to WHNF.

Used in getVariables to reply to a variable introspection request.

deepseqTerm :: Term -> Debugger Term Source #

Evaluate a Term to NF

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

freshInt :: Debugger Int Source #

Generate a new unique Int

liftGhc :: Ghc a -> Debugger a Source #

Lift a Ghc action into a Debugger one.