ghc-debugger
Safe HaskellNone
LanguageHaskell2010

GHC.Debugger.Interface.Messages

Description

Types for sending and receiving messages to/from ghc-debugger

Synopsis

Documentation

data Command Source #

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 setBreakpoints re-sets all breakpoints from zero for a source rather than incrementally.

Fields

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 EntryPoint is Main, runArgs are set as process invocation arguments (as in argv) rather than passed directly as a Haskell function arguments.

TerminateProcess

Terminate ghc-debugger and exit

Instances

Instances details
FromJSON Command Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON Command Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic Command Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep Command 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep Command = D1 ('MetaData "Command" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0-inplace" 'False) (((C1 ('MetaCons "SetBreakpoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Breakpoint)) :+: (C1 ('MetaCons "DelBreakpoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Breakpoint)) :+: C1 ('MetaCons "GetBreakpointsAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Breakpoint)))) :+: ((C1 ('MetaCons "ClearModBreakpoints" 'PrefixI 'True) (S1 ('MetaSel ('Just "file") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "ClearFunctionBreakpoints" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GetStacktrace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GetScopes" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "GetVariables" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VariableReference)) :+: (C1 ('MetaCons "DoEval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "DoContinue" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DoStepLocal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoSingleStep" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DebugExecution" 'PrefixI 'True) (S1 ('MetaSel ('Just "entryPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntryPoint) :*: S1 ('MetaSel ('Just "runArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "TerminateProcess" 'PrefixI 'False) (U1 :: Type -> Type)))))

Methods

from :: Command -> Rep Command x #

to :: Rep Command x -> Command #

Show Command Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep Command Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep Command = D1 ('MetaData "Command" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0-inplace" 'False) (((C1 ('MetaCons "SetBreakpoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Breakpoint)) :+: (C1 ('MetaCons "DelBreakpoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Breakpoint)) :+: C1 ('MetaCons "GetBreakpointsAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Breakpoint)))) :+: ((C1 ('MetaCons "ClearModBreakpoints" 'PrefixI 'True) (S1 ('MetaSel ('Just "file") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "ClearFunctionBreakpoints" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GetStacktrace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GetScopes" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "GetVariables" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VariableReference)) :+: (C1 ('MetaCons "DoEval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "DoContinue" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DoStepLocal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoSingleStep" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DebugExecution" 'PrefixI 'True) (S1 ('MetaSel ('Just "entryPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntryPoint) :*: S1 ('MetaSel ('Just "runArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :+: C1 ('MetaCons "TerminateProcess" 'PrefixI 'False) (U1 :: Type -> Type)))))

data EntryPoint Source #

An entry point for program execution.

Constructors

MainEntry 

Fields

FunctionEntry 

Fields

Instances

Instances details
FromJSON EntryPoint Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON EntryPoint Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic EntryPoint Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep EntryPoint 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep EntryPoint = D1 ('MetaData "EntryPoint" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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)))
Show EntryPoint Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep EntryPoint Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep EntryPoint = D1 ('MetaData "EntryPoint" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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

Instances details
FromJSON Breakpoint Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON Breakpoint Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic Breakpoint Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep Breakpoint 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep Breakpoint = D1 ('MetaData "Breakpoint" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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)))
Show Breakpoint Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep Breakpoint Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep Breakpoint = D1 ('MetaData "Breakpoint" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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)))

data ScopeInfo Source #

Information about a scope

Instances

Instances details
FromJSON ScopeInfo Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON ScopeInfo Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic ScopeInfo Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep ScopeInfo 
Instance details

Defined in GHC.Debugger.Interface.Messages

Show ScopeInfo Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep ScopeInfo Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

data VarFields Source #

Instances

Instances details
FromJSON VarFields Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON VarFields Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Eq VarFields Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic VarFields Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep VarFields 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep VarFields = D1 ('MetaData "VarFields" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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)))
Show VarFields Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep VarFields Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep VarFields = D1 ('MetaData "VarFields" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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)))

data VarInfo Source #

Information about a variable

Constructors

VarInfo 

Fields

Instances

Instances details
FromJSON VarInfo Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON VarInfo Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Eq VarInfo Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Methods

(==) :: VarInfo -> VarInfo -> Bool #

(/=) :: VarInfo -> VarInfo -> Bool #

Generic VarInfo Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Methods

from :: VarInfo -> Rep VarInfo x #

to :: Rep VarInfo x -> VarInfo #

Show VarInfo Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep VarInfo Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

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

Instances details
FromJSON BreakpointKind Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON BreakpointKind Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Eq BreakpointKind Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic BreakpointKind Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep BreakpointKind 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep BreakpointKind = D1 ('MetaData "BreakpointKind" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0-inplace" 'False) (C1 ('MetaCons "ModuleBreakpointKind" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FunctionBreakpointKind" 'PrefixI 'False) (U1 :: Type -> Type))
Show BreakpointKind Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep BreakpointKind Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep BreakpointKind = D1 ('MetaData "BreakpointKind" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.0-inplace" 'False) (C1 ('MetaCons "ModuleBreakpointKind" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FunctionBreakpointKind" 'PrefixI 'False) (U1 :: Type -> Type))

data ScopeVariablesReference Source #

Referring to existing scopes

Instances

Instances details
FromJSON ScopeVariablesReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON ScopeVariablesReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Eq ScopeVariablesReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Ord ScopeVariablesReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic ScopeVariablesReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep ScopeVariablesReference 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep ScopeVariablesReference = D1 ('MetaData "ScopeVariablesReference" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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)))
Show ScopeVariablesReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep ScopeVariablesReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep ScopeVariablesReference = D1 ('MetaData "ScopeVariablesReference" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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

Instances details
FromJSON VariableReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON VariableReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Eq VariableReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Ord VariableReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Bounded VariableReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Enum VariableReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic VariableReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep VariableReference 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep VariableReference = D1 ('MetaData "VariableReference" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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)))))
Show VariableReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep VariableReference Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep VariableReference = D1 ('MetaData "VariableReference" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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 

Fields

Instances

Instances details
FromJSON SourceSpan Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON SourceSpan Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic SourceSpan Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep SourceSpan 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep SourceSpan = D1 ('MetaData "SourceSpan" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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)))))
Show SourceSpan Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep SourceSpan Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep SourceSpan = D1 ('MetaData "SourceSpan" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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)))))

data Response Source #

The responses sent by `ghc-debugger` to the client

Instances

Instances details
FromJSON Response Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON Response Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic Response Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep Response 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep Response = D1 ('MetaData "Response" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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)))))

Methods

from :: Response -> Rep Response x #

to :: Rep Response x -> Response #

Show Response Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep Response Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep Response = D1 ('MetaData "Response" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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.

Fields

  • changed :: Bool

    Did the status of the found breakpoint change?

BreakNotFound

No breakpoints found

ManyBreaksFound [BreakFound]

Found many breakpoints. Caused by setting breakpoint on a name with multiple matches or many equations.

Instances

Instances details
FromJSON BreakFound Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON BreakFound Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic BreakFound Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep BreakFound 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep BreakFound = D1 ('MetaData "BreakFound" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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]))))
Show BreakFound Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep BreakFound Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep BreakFound = D1 ('MetaData "BreakFound" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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 
EvalException 
EvalStopped 

Fields

EvalAbortedWith String

Evaluation failed for some reason other than completedcompleted-with-exceptionstopped.

Instances

Instances details
FromJSON EvalResult Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON EvalResult Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic EvalResult Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep EvalResult 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep EvalResult = D1 ('MetaData "EvalResult" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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))))
Show EvalResult Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep EvalResult Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep EvalResult = D1 ('MetaData "EvalResult" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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

Instances details
FromJSON StackFrame Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

ToJSON StackFrame Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Generic StackFrame Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

Associated Types

type Rep StackFrame 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep StackFrame = D1 ('MetaData "StackFrame" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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)))
Show StackFrame Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep StackFrame Source # 
Instance details

Defined in GHC.Debugger.Interface.Messages

type Rep StackFrame = D1 ('MetaData "StackFrame" "GHC.Debugger.Interface.Messages" "ghc-debugger-0.1.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