Safe Haskell | None |
---|---|
Language | Haskell2010 |
GHC.Debugger.Interface.Messages
Contents
Description
Types for sending and receiving messages to/from ghc-debugger
Synopsis
- data Command
- = SetBreakpoint Breakpoint
- | DelBreakpoint Breakpoint
- | GetBreakpointsAt Breakpoint
- | ClearModBreakpoints { }
- | ClearFunctionBreakpoints
- | GetStacktrace
- | GetScopes
- | GetVariables VariableReference
- | DoEval String
- | DoContinue
- | DoStepLocal
- | DoSingleStep
- | DebugExecution {
- entryPoint :: EntryPoint
- runArgs :: [String]
- | TerminateProcess
- data EntryPoint
- data Breakpoint
- data ScopeInfo = ScopeInfo {}
- data VarFields
- = LabeledFields [VarInfo]
- | IndexedFields [VarInfo]
- | NoFields
- data VarInfo = VarInfo {}
- data BreakpointKind
- data ScopeVariablesReference
- data VariableReference
- data SourceSpan = SourceSpan {}
- data Response
- = DidEval EvalResult
- | DidSetBreakpoint BreakFound
- | DidRemoveBreakpoint BreakFound
- | DidGetBreakpoints (Maybe SourceSpan)
- | DidClearBreakpoints
- | DidContinue EvalResult
- | DidStep EvalResult
- | DidExec EvalResult
- | GotStacktrace [StackFrame]
- | GotScopes [ScopeInfo]
- | GotVariables (Either VarInfo [VarInfo])
- | Aborted String
- | Initialised
- data BreakFound
- = BreakFound {
- changed :: !Bool
- breakId :: BreakpointId
- sourceSpan :: SourceSpan
- | BreakFoundNoLoc { }
- | BreakNotFound
- | ManyBreaksFound [BreakFound]
- = BreakFound {
- data EvalResult
- = EvalCompleted {
- resultVal :: String
- resultType :: String
- | EvalException {
- resultVal :: String
- resultType :: String
- | EvalStopped { }
- | EvalAbortedWith String
- = EvalCompleted {
- data StackFrame = StackFrame {
- name :: String
- sourceSpan :: SourceSpan
Documentation
The commands sent to ghc debugger
Constructors
SetBreakpoint Breakpoint | Set a breakpoint on a given function, or module by line number |
DelBreakpoint Breakpoint | Delete a breakpoint on a given function, or module by line number |
GetBreakpointsAt Breakpoint | Find the valid breakpoints locations for the given module Breakpoint |
ClearModBreakpoints | Clear all breakpoints in the specified file.
This is useful because DAP's |
ClearFunctionBreakpoints | Clear all function breakpoints |
GetStacktrace | Get the evaluation stacktrace until the current breakpoint. |
GetScopes | Get the list of available scopes at the current breakpoint |
GetVariables VariableReference | Get the variables in scope for the current breakpoint. Note: for GHCs <9.13 this only reports the variables free in the expression we're stopped at rather than all variables in scope. |
DoEval String | Evaluate an expression at the current breakpoint. |
DoContinue | Continue executing from the current breakpoint |
DoStepLocal | Step local, which executes until next breakpoint in the same function. |
DoSingleStep | Single step always to the next breakpoint. Used for "step-in". |
DebugExecution | Execute a prog with debugging enabled. Breaks on the existing breakpoints. Constructed with an entry point function name and the arguments to pass it. When the |
Fields
| |
TerminateProcess | Terminate ghc-debugger and exit |
Instances
data EntryPoint Source #
An entry point for program execution.
Instances
FromJSON EntryPoint Source # | |||||
Defined in GHC.Debugger.Interface.Messages | |||||
ToJSON EntryPoint Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods toJSON :: EntryPoint -> Value # toEncoding :: EntryPoint -> Encoding # toJSONList :: [EntryPoint] -> Value # toEncodingList :: [EntryPoint] -> Encoding # omitField :: EntryPoint -> Bool # | |||||
Generic EntryPoint Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
| |||||
Show EntryPoint Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods showsPrec :: Int -> EntryPoint -> ShowS # show :: EntryPoint -> String # showList :: [EntryPoint] -> ShowS # | |||||
type Rep EntryPoint Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep EntryPoint = D1 ('MetaData "EntryPoint" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) (C1 ('MetaCons "MainEntry" 'PrefixI 'True) (S1 ('MetaSel ('Just "mainName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :+: C1 ('MetaCons "FunctionEntry" 'PrefixI 'True) (S1 ('MetaSel ('Just "fnName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) |
data Breakpoint Source #
A breakpoint can be set/removed on functions by name, or in modules by line number. And, globally, for all exceptions, or just uncaught exceptions.
Instances
FromJSON Breakpoint Source # | |||||
Defined in GHC.Debugger.Interface.Messages | |||||
ToJSON Breakpoint Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods toJSON :: Breakpoint -> Value # toEncoding :: Breakpoint -> Encoding # toJSONList :: [Breakpoint] -> Value # toEncodingList :: [Breakpoint] -> Encoding # omitField :: Breakpoint -> Bool # | |||||
Generic Breakpoint Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
| |||||
Show Breakpoint Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods showsPrec :: Int -> Breakpoint -> ShowS # show :: Breakpoint -> String # showList :: [Breakpoint] -> ShowS # | |||||
type Rep Breakpoint Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep Breakpoint = D1 ('MetaData "Breakpoint" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "ModuleBreak" 'PrefixI 'True) (S1 ('MetaSel ('Just "path") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "lineNum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "columnNum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))) :+: C1 ('MetaCons "FunctionBreak" 'PrefixI 'True) (S1 ('MetaSel ('Just "function") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "OnExceptionsBreak" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OnUncaughtExceptionsBreak" 'PrefixI 'False) (U1 :: Type -> Type))) |
Information about a scope
Constructors
ScopeInfo | |
Fields
|
Instances
FromJSON ScopeInfo Source # | |||||
Defined in GHC.Debugger.Interface.Messages | |||||
ToJSON ScopeInfo Source # | |||||
Generic ScopeInfo Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
| |||||
Show ScopeInfo Source # | |||||
type Rep ScopeInfo Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep ScopeInfo = D1 ('MetaData "ScopeInfo" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ScopeInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "kind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScopeVariablesReference) :*: S1 ('MetaSel ('Just "sourceSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceSpan)) :*: (S1 ('MetaSel ('Just "numVars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "expensive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) |
Constructors
LabeledFields [VarInfo] | |
IndexedFields [VarInfo] | |
NoFields |
Instances
FromJSON VarFields Source # | |||||
Defined in GHC.Debugger.Interface.Messages | |||||
ToJSON VarFields Source # | |||||
Eq VarFields Source # | |||||
Generic VarFields Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
| |||||
Show VarFields Source # | |||||
type Rep VarFields Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep VarFields = D1 ('MetaData "VarFields" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LabeledFields" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarInfo])) :+: (C1 ('MetaCons "IndexedFields" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarInfo])) :+: C1 ('MetaCons "NoFields" 'PrefixI 'False) (U1 :: Type -> Type))) |
Information about a variable
Constructors
VarInfo | |
Instances
FromJSON VarInfo Source # | |||||
Defined in GHC.Debugger.Interface.Messages | |||||
ToJSON VarInfo Source # | |||||
Eq VarInfo Source # | |||||
Generic VarInfo Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
| |||||
Show VarInfo Source # | |||||
type Rep VarInfo Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep VarInfo = D1 ('MetaData "VarInfo" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) (C1 ('MetaCons "VarInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "varName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "varType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "varValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :*: (S1 ('MetaSel ('Just "isThunk") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "varRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VariableReference) :*: S1 ('MetaSel ('Just "varFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarFields))))) |
data BreakpointKind Source #
What kind of breakpoint are we referring to, module or function breakpoints?
Used e.g. in the ClearBreakpoints
request
Constructors
ModuleBreakpointKind | Module breakpoints |
FunctionBreakpointKind | Function breakpoints |
Instances
FromJSON BreakpointKind Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods parseJSON :: Value -> Parser BreakpointKind # parseJSONList :: Value -> Parser [BreakpointKind] # | |||||
ToJSON BreakpointKind Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods toJSON :: BreakpointKind -> Value # toEncoding :: BreakpointKind -> Encoding # toJSONList :: [BreakpointKind] -> Value # toEncodingList :: [BreakpointKind] -> Encoding # omitField :: BreakpointKind -> Bool # | |||||
Eq BreakpointKind Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods (==) :: BreakpointKind -> BreakpointKind -> Bool # (/=) :: BreakpointKind -> BreakpointKind -> Bool # | |||||
Generic BreakpointKind Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
Methods from :: BreakpointKind -> Rep BreakpointKind x # to :: Rep BreakpointKind x -> BreakpointKind # | |||||
Show BreakpointKind Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods showsPrec :: Int -> BreakpointKind -> ShowS # show :: BreakpointKind -> String # showList :: [BreakpointKind] -> ShowS # | |||||
type Rep BreakpointKind Source # | |||||
Defined in GHC.Debugger.Interface.Messages |
data ScopeVariablesReference Source #
Referring to existing scopes
Instances
FromJSON ScopeVariablesReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods parseJSON :: Value -> Parser ScopeVariablesReference # parseJSONList :: Value -> Parser [ScopeVariablesReference] # | |||||
ToJSON ScopeVariablesReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods toJSON :: ScopeVariablesReference -> Value # toEncoding :: ScopeVariablesReference -> Encoding # toJSONList :: [ScopeVariablesReference] -> Value # | |||||
Eq ScopeVariablesReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods (==) :: ScopeVariablesReference -> ScopeVariablesReference -> Bool # (/=) :: ScopeVariablesReference -> ScopeVariablesReference -> Bool # | |||||
Ord ScopeVariablesReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods compare :: ScopeVariablesReference -> ScopeVariablesReference -> Ordering # (<) :: ScopeVariablesReference -> ScopeVariablesReference -> Bool # (<=) :: ScopeVariablesReference -> ScopeVariablesReference -> Bool # (>) :: ScopeVariablesReference -> ScopeVariablesReference -> Bool # (>=) :: ScopeVariablesReference -> ScopeVariablesReference -> Bool # max :: ScopeVariablesReference -> ScopeVariablesReference -> ScopeVariablesReference # min :: ScopeVariablesReference -> ScopeVariablesReference -> ScopeVariablesReference # | |||||
Generic ScopeVariablesReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
Methods from :: ScopeVariablesReference -> Rep ScopeVariablesReference x # to :: Rep ScopeVariablesReference x -> ScopeVariablesReference # | |||||
Show ScopeVariablesReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods showsPrec :: Int -> ScopeVariablesReference -> ShowS # show :: ScopeVariablesReference -> String # showList :: [ScopeVariablesReference] -> ShowS # | |||||
type Rep ScopeVariablesReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep ScopeVariablesReference = D1 ('MetaData "ScopeVariablesReference" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LocalVariablesScope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ModuleVariablesScope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GlobalVariablesScope" 'PrefixI 'False) (U1 :: Type -> Type))) |
data VariableReference Source #
The type of variables referenced, or a particular variable referenced for its fields or value (when inspecting a thunk)
Constructors
NoVariables | A void reference to nothing at all. Used e.g. for ty cons and data cons |
LocalVariables | Variables in the local context (includes arguments, previous bindings) |
ModuleVariables | Variables in the module where we're stopped |
GlobalVariables | Variables in the global context |
SpecificVariable Int | A reference to a specific variable. Used to force its result or get its structured children |
Instances
FromJSON VariableReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods parseJSON :: Value -> Parser VariableReference # parseJSONList :: Value -> Parser [VariableReference] # | |||||
ToJSON VariableReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods toJSON :: VariableReference -> Value # toEncoding :: VariableReference -> Encoding # toJSONList :: [VariableReference] -> Value # toEncodingList :: [VariableReference] -> Encoding # omitField :: VariableReference -> Bool # | |||||
Eq VariableReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods (==) :: VariableReference -> VariableReference -> Bool # (/=) :: VariableReference -> VariableReference -> Bool # | |||||
Ord VariableReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods compare :: VariableReference -> VariableReference -> Ordering # (<) :: VariableReference -> VariableReference -> Bool # (<=) :: VariableReference -> VariableReference -> Bool # (>) :: VariableReference -> VariableReference -> Bool # (>=) :: VariableReference -> VariableReference -> Bool # max :: VariableReference -> VariableReference -> VariableReference # min :: VariableReference -> VariableReference -> VariableReference # | |||||
Bounded VariableReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages | |||||
Enum VariableReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods succ :: VariableReference -> VariableReference # pred :: VariableReference -> VariableReference # toEnum :: Int -> VariableReference # fromEnum :: VariableReference -> Int # enumFrom :: VariableReference -> [VariableReference] # enumFromThen :: VariableReference -> VariableReference -> [VariableReference] # enumFromTo :: VariableReference -> VariableReference -> [VariableReference] # enumFromThenTo :: VariableReference -> VariableReference -> VariableReference -> [VariableReference] # | |||||
Generic VariableReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
Methods from :: VariableReference -> Rep VariableReference x # to :: Rep VariableReference x -> VariableReference # | |||||
Show VariableReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods showsPrec :: Int -> VariableReference -> ShowS # show :: VariableReference -> String # showList :: [VariableReference] -> ShowS # | |||||
type Rep VariableReference Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep VariableReference = D1 ('MetaData "VariableReference" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "NoVariables" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LocalVariables" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ModuleVariables" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GlobalVariables" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SpecificVariable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) |
data SourceSpan Source #
A source span type for the interface. Like RealSrcSpan
.
Constructors
SourceSpan | |
Instances
FromJSON SourceSpan Source # | |||||
Defined in GHC.Debugger.Interface.Messages | |||||
ToJSON SourceSpan Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods toJSON :: SourceSpan -> Value # toEncoding :: SourceSpan -> Encoding # toJSONList :: [SourceSpan] -> Value # toEncodingList :: [SourceSpan] -> Encoding # omitField :: SourceSpan -> Bool # | |||||
Generic SourceSpan Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
| |||||
Show SourceSpan Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods showsPrec :: Int -> SourceSpan -> ShowS # show :: SourceSpan -> String # showList :: [SourceSpan] -> ShowS # | |||||
type Rep SourceSpan Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep SourceSpan = D1 ('MetaData "SourceSpan" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SourceSpan" 'PrefixI 'True) ((S1 ('MetaSel ('Just "file") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "startLine") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "endLine") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "startCol") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "endCol") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int))))) |
The responses sent by `ghc-debugger` to the client
Constructors
DidEval EvalResult | |
DidSetBreakpoint BreakFound | |
DidRemoveBreakpoint BreakFound | |
DidGetBreakpoints (Maybe SourceSpan) | |
DidClearBreakpoints | |
DidContinue EvalResult | |
DidStep EvalResult | |
DidExec EvalResult | |
GotStacktrace [StackFrame] | |
GotScopes [ScopeInfo] | |
GotVariables (Either VarInfo [VarInfo]) | |
Aborted String | |
Initialised |
Instances
FromJSON Response Source # | |||||
Defined in GHC.Debugger.Interface.Messages | |||||
ToJSON Response Source # | |||||
Generic Response Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
| |||||
Show Response Source # | |||||
type Rep Response Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep Response = D1 ('MetaData "Response" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) (((C1 ('MetaCons "DidEval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EvalResult)) :+: (C1 ('MetaCons "DidSetBreakpoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BreakFound)) :+: C1 ('MetaCons "DidRemoveBreakpoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BreakFound)))) :+: (C1 ('MetaCons "DidGetBreakpoints" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SourceSpan))) :+: (C1 ('MetaCons "DidClearBreakpoints" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DidContinue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EvalResult))))) :+: ((C1 ('MetaCons "DidStep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EvalResult)) :+: (C1 ('MetaCons "DidExec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EvalResult)) :+: C1 ('MetaCons "GotStacktrace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [StackFrame])))) :+: ((C1 ('MetaCons "GotScopes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ScopeInfo])) :+: C1 ('MetaCons "GotVariables" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either VarInfo [VarInfo])))) :+: (C1 ('MetaCons "Aborted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Initialised" 'PrefixI 'False) (U1 :: Type -> Type))))) |
data BreakFound Source #
Constructors
BreakFound | |
Fields
| |
BreakFoundNoLoc | Breakpoint found but without location info. This happens when setting breakpoints on exceptions. |
BreakNotFound | No breakpoints found |
ManyBreaksFound [BreakFound] | Found many breakpoints. Caused by setting breakpoint on a name with multiple matches or many equations. |
Instances
FromJSON BreakFound Source # | |||||
Defined in GHC.Debugger.Interface.Messages | |||||
ToJSON BreakFound Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods toJSON :: BreakFound -> Value # toEncoding :: BreakFound -> Encoding # toJSONList :: [BreakFound] -> Value # toEncodingList :: [BreakFound] -> Encoding # omitField :: BreakFound -> Bool # | |||||
Generic BreakFound Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
| |||||
Show BreakFound Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods showsPrec :: Int -> BreakFound -> ShowS # show :: BreakFound -> String # showList :: [BreakFound] -> ShowS # | |||||
type Rep BreakFound Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep BreakFound = D1 ('MetaData "BreakFound" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "BreakFound" 'PrefixI 'True) (S1 ('MetaSel ('Just "changed") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "breakId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BreakpointId) :*: S1 ('MetaSel ('Just "sourceSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceSpan))) :+: C1 ('MetaCons "BreakFoundNoLoc" 'PrefixI 'True) (S1 ('MetaSel ('Just "changed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: (C1 ('MetaCons "BreakNotFound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ManyBreaksFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BreakFound])))) |
data EvalResult Source #
Constructors
EvalCompleted | |
Fields
| |
EvalException | |
Fields
| |
EvalStopped | |
Fields
| |
EvalAbortedWith String | Evaluation failed for some reason other than completedcompleted-with-exceptionstopped. |
Instances
FromJSON EvalResult Source # | |||||
Defined in GHC.Debugger.Interface.Messages | |||||
ToJSON EvalResult Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods toJSON :: EvalResult -> Value # toEncoding :: EvalResult -> Encoding # toJSONList :: [EvalResult] -> Value # toEncodingList :: [EvalResult] -> Encoding # omitField :: EvalResult -> Bool # | |||||
Generic EvalResult Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
| |||||
Show EvalResult Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods showsPrec :: Int -> EvalResult -> ShowS # show :: EvalResult -> String # showList :: [EvalResult] -> ShowS # | |||||
type Rep EvalResult Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep EvalResult = D1 ('MetaData "EvalResult" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "EvalCompleted" 'PrefixI 'True) (S1 ('MetaSel ('Just "resultVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "resultType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "EvalException" 'PrefixI 'True) (S1 ('MetaSel ('Just "resultVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "resultType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "EvalStopped" 'PrefixI 'True) (S1 ('MetaSel ('Just "breakId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BreakpointId))) :+: C1 ('MetaCons "EvalAbortedWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) |
data StackFrame Source #
Constructors
StackFrame | |
Fields
|
Instances
FromJSON StackFrame Source # | |||||
Defined in GHC.Debugger.Interface.Messages | |||||
ToJSON StackFrame Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods toJSON :: StackFrame -> Value # toEncoding :: StackFrame -> Encoding # toJSONList :: [StackFrame] -> Value # toEncodingList :: [StackFrame] -> Encoding # omitField :: StackFrame -> Bool # | |||||
Generic StackFrame Source # | |||||
Defined in GHC.Debugger.Interface.Messages Associated Types
| |||||
Show StackFrame Source # | |||||
Defined in GHC.Debugger.Interface.Messages Methods showsPrec :: Int -> StackFrame -> ShowS # show :: StackFrame -> String # showList :: [StackFrame] -> ShowS # | |||||
type Rep StackFrame Source # | |||||
Defined in GHC.Debugger.Interface.Messages type Rep StackFrame = D1 ('MetaData "StackFrame" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0.0-inplace" 'False) (C1 ('MetaCons "StackFrame" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "sourceSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceSpan))) |
Orphan instances
FromJSON BreakpointId Source # | |
ToJSON BreakpointId Source # | |
Methods toJSON :: BreakpointId -> Value # toEncoding :: BreakpointId -> Encoding # toJSONList :: [BreakpointId] -> Value # toEncodingList :: [BreakpointId] -> Encoding # omitField :: BreakpointId -> Bool # | |
Show BreakpointId Source # | |
Methods showsPrec :: Int -> BreakpointId -> ShowS # show :: BreakpointId -> String # showList :: [BreakpointId] -> ShowS # |