haskell-dap-0.0.13.0: Haskell implementation of the DAP interface data.

Copyright2017-2019 phoityne_hs
LicenseBSD3
Safe HaskellSafe
LanguageHaskell2010

Haskell.DAP

Contents

Description

Synopsis

commons

_THREAD_ID :: Int Source #

The debugee thread id is fixed 0.

data Request Source #

Client-initiated request

Constructors

Request 

Fields

Instances
Eq Request Source # 
Instance details

Defined in Haskell.DAP

Methods

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

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

Read Request Source # 
Instance details

Defined in Haskell.DAP

Show Request Source # 
Instance details

Defined in Haskell.DAP

data Response Source #

Response for a request.

Constructors

Response 

Fields

Instances
Eq Response Source # 
Instance details

Defined in Haskell.DAP

Read Response Source # 
Instance details

Defined in Haskell.DAP

Show Response Source # 
Instance details

Defined in Haskell.DAP

data ColumnDescriptor Source #

A ColumnDescriptor specifies what module attribute to show in a column of the ModulesView,

how to format it, and what the column's label should be.

It is only used if the underlying UI actually supports this level of customization.

Constructors

ColumnDescriptor 

Fields

data Source Source #

A Source is a descriptor for source code.

It is returned from the debug adapter as part of a StackFrame and it is used by clients

when specifying breakpoints.

Constructors

Source 

Fields

  • nameSource :: Maybe String

    The short name of the source. Every source returned from the debug adapter has a name. When sending a source to the debug adapter this name is optional.

  • pathSource :: String

    The path of the source to be shown in the UI. It is only used to locate and load the content of the source if no sourceReference is specified (or its vaule is 0).

  • sourceReferenceSource :: Maybe Int

    If sourceReference > 0 the contents of the source must be retrieved through the SourceRequest (even if a path is specified). A sourceReference is only valid for a session, so it must not be used to persist a source.

  • origineSource :: Maybe String

    The (optional) origin of this source: possible values 'internal module', 'inlined content from source map', etc.

Instances
Eq Source Source # 
Instance details

Defined in Haskell.DAP

Methods

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

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

Read Source Source # 
Instance details

Defined in Haskell.DAP

Show Source Source # 
Instance details

Defined in Haskell.DAP

data Breakpoint Source #

Information about a Breakpoint created in setBreakpoints or setFunctionBreakpoints.

Constructors

Breakpoint 

Fields

  • idBreakpoint :: Maybe Int

    An optional unique identifier for the breakpoint.

  • verifiedBreakpoint :: Bool

    If true breakpoint could be set (but not necessarily at the desired location).

  • messageBreakpoint :: String

    An optional message about the state of the breakpoint. This is shown to the user and can be used to explain why a breakpoint could not be verified.

  • sourceBreakpoint :: Source

    The source where the breakpoint is located.

  • lineBreakpoint :: Int

    The start line of the actual range covered by the breakpoint.

  • columnBreakpoint :: Int

    An optional start column of the actual range covered by the breakpoint.

  • endLineBreakpoint :: Int

    An optional end line of the actual range covered by the breakpoint.

  • endColumnBreakpoint :: Int

    An optional end column of the actual range covered by the breakpoint. If no end line is given, then the end column is assumed to be in the start line.

data ExceptionBreakpointsFilter Source #

An ExceptionBreakpointsFilter is shown in the UI as an option for configuring how exceptions are dealt with.

Constructors

ExceptionBreakpointsFilter 

Fields

initialize

data InitializeRequest Source #

Initialize request; value of command field is initialize.

The initialize request is sent as the first request from the client to the debug adapter in order to configure it with client capabilities and to retrieve capabilities from the debug adapter.

Until the debug adapter has responded to with an initialize response, the client must not send any additional requests or events to the debug adapter. In addition the debug adapter is not allowed to send any requests or events to the client until it has responded with an initialize response.

The initialize request may only be sent once.

Constructors

InitializeRequest 

Fields

data InitializeRequestArguments Source #

Arguments for initialize request.

Constructors

InitializeRequestArguments 

Fields

data InitializeResponse Source #

Response to initialize request.

Constructors

InitializeResponse 

Fields

data InitializeResponseBody Source #

Information about the capabilities of a debug adapter.

Constructors

InitializeResponseBody 

Fields

disconnect

data DisconnectRequest Source #

Disconnect request; value of command field is disconnect.

The disconnect request is sent from the client to the debug adapter in order to stop debugging.

It asks the debug adapter to disconnect from the debuggee and to terminate the debug adapter.

If the debuggee has been started with the launch request, the disconnect request terminates the debuggee.

If the attach request was used to connect to the debuggee, disconnect does not terminate the debuggee.

This behavior can be controlled with the terminateDebuggee argument (if supported by the debug adapter).

Constructors

DisconnectRequest 

Fields

data DisconnectResponse Source #

Response to disconnect request. This is just an acknowledgement, so no body field is required.

Constructors

DisconnectResponse 

Fields

pause

data PauseRequest Source #

Pause request; value of command field is "pause".

The request suspenses the debuggee.

The debug adapter first sends the response and then a stopped event (with reason pause) after the thread has been paused successfully.

Constructors

PauseRequest 

Fields

data PauseResponse Source #

Response to "pause" request. This is just an acknowledgement, so no body field is required.

Constructors

PauseResponse 

Fields

terminate

data TerminateRequest Source #

Terminate request; value of command field is terminate.

The terminate request is sent from the client to the debug adapter in order to give the debuggee a chance for terminating itself.

Constructors

TerminateRequest 

Fields

data TerminateResponse Source #

Response to terminate request. This is just an acknowledgement, so no body field is required.

Constructors

TerminateResponse 

Fields

launch

data LaunchRequest Source #

Launch request; value of command field is launch.

The launch request is sent from the client to the debug adapter to start the debuggee with or without debugging (if noDebug is true).

Since launching is debugger/runtime specific, the arguments for this request are not part of this specification.

Constructors

LaunchRequest 

Fields

data LaunchRequestArguments Source #

Arguments for launch request. Additional attributes are implementation specific.

Constructors

LaunchRequestArguments 

Fields

data LaunchResponse Source #

Response to launch request. This is just an acknowledgement, so no body field is required.

Constructors

LaunchResponse 

Fields

setBreakpoints

data SourceBreakpoint Source #

Properties of a breakpoint passed to the setBreakpoints request.

Constructors

SourceBreakpoint 

Fields

data SetBreakpointsRequest Source #

SetBreakpoints request; value of command field is "setBreakpoints".

Sets multiple breakpoints for a single source and clears all previous breakpoints in that source.

To clear all breakpoint for a source, specify an empty array.

When a breakpoint is hit, a StoppedEvent (event type breakpoint) is generated.

Constructors

SetBreakpointsRequest 

Fields

data SetBreakpointsResponse Source #

Response to "setBreakpoints" request.

Returned is information about each breakpoint created by this request.

This includes the actual code location and whether the breakpoint could be verified.

The breakpoints returned are in the same order as the elements of the breakpoints

(or the deprecated lines) in the SetBreakpointsRequestArguments.

Constructors

SetBreakpointsResponse 

Fields

data SetBreakpointsResponseBody Source #

Response to "setBreakpoints" request.

Returned is information about each breakpoint created by this request.

This includes the actual code location and whether the breakpoint could be verified.

The breakpoints returned are in the same order as the elements of the breakpoints

(or the deprecated lines) in the SetBreakpointsRequestArguments.

Constructors

SetBreakpointsResponseBody 

Fields

setFunctionBreakpoints

data SetFunctionBreakpointsRequest Source #

SetFunctionBreakpoints request; value of command field is "setFunctionBreakpoints".

Sets multiple function breakpoints and clears all previous function breakpoints.

To clear all function breakpoint, specify an empty array.

When a function breakpoint is hit, a StoppedEvent (event type 'function breakpoint') is generated.

Constructors

SetFunctionBreakpointsRequest 

Fields

data SetFunctionBreakpointsResponse Source #

Response to "setFunctionBreakpoints" request.

Constructors

SetFunctionBreakpointsResponse 

Fields

setExceptionBreakpoints

data SetExceptionBreakpointsRequest Source #

SetExceptionBreakpoints request; value of command field is setExceptionBreakpoints.

The request configures the debuggers response to thrown exceptions. If an exception is configured to break,

a StoppedEvent is fired (event type exception).

Constructors

SetExceptionBreakpointsRequest 

Fields

data SetExceptionBreakpointsResponse Source #

Response to setExceptionBreakpoints request. This is just an acknowledgement, so no body field is required.

Constructors

SetExceptionBreakpointsResponse 

Fields

configurationDone

data ConfigurationDoneRequest Source #

ConfigurationDone request; value of command field is configurationDone.

The client of the debug protocol must send this request at the end of the sequence of configuration requests

(which was started by the InitializedEvent).

Constructors

ConfigurationDoneRequest 

Fields

data ConfigurationDoneResponse Source #

Response to configurationDone request. This is just an acknowledgement, so no body field is required.

Constructors

ConfigurationDoneResponse 

Fields

threads

data ThreadsRequest Source #

Thread request; value of command field is "threads".

The request retrieves a list of all threads.

Constructors

ThreadsRequest 

Fields

data Thread Source #

A Thread is a name/value pair.

If the value is structured (has children), a handle is provided to retrieve the children with the ThreadsRequest.

Constructors

Thread 

Fields

Instances
Eq Thread Source # 
Instance details

Defined in Haskell.DAP

Methods

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

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

Read Thread Source # 
Instance details

Defined in Haskell.DAP

Show Thread Source # 
Instance details

Defined in Haskell.DAP

data ThreadsResponse Source #

Response to "threads" request.

Constructors

ThreadsResponse 

Fields

stackTrace

data StackTraceRequest Source #

StackTrace request; value of command field is "stackTrace".

The request returns a stacktrace from the current execution state.

Constructors

StackTraceRequest 

Fields

data StackTraceRequestArguments Source #

Arguments for stackTrace request.

Constructors

StackTraceRequestArguments 

Fields

data StackFrame Source #

A Stackframe contains the source location.

Constructors

StackFrame 

Fields

  • idStackFrame :: Int

    An identifier for the stack frame. It must be unique across all threads. This id can be used to retrieve the scopes of the frame with the scopesRequest or to restart the execution of a stackframe.

  • nameStackFrame :: String

    The name of the stack frame, typically a method name.

  • sourceStackFrame :: Source

    The optional source of the frame.

  • lineStackFrame :: Int

    The line within the file of the frame. If source is null or doesn't exist, line is 0 and must be ignored.

  • columnStackFrame :: Int

    The column within the line. If source is null or doesn't exist, column is 0 and must be ignored.

  • endLineStackFrame :: Int

    An optional end line of the range covered by the stack frame.

  • endColumnStackFrame :: Int

    An optional end column of the range covered by the stack frame.

data StackTraceResponse Source #

Response to "stackTrace" request.

Constructors

StackTraceResponse 

Fields

data StackTraceResponseBody Source #

Response to stackTrace request.

Constructors

StackTraceResponseBody 

Fields

scopes

data ScopesRequest Source #

Scopes request; value of command field is "scopes".

The request returns the variable scopes for a given stackframe ID.

Constructors

ScopesRequest 

Fields

data Scope Source #

A Scope is a named container for variables. Optionally a scope can map to a source or a range within a source.

Constructors

Scope 

Fields

  • nameScope :: String

    Name of the scope such as Arguments, Locals.

  • variablesReferenceScope :: Int

    The variables of this scope can be retrieved by passing the value of variablesReference to the VariablesRequest.

  • namedVariablesScope :: Maybe Int

    The number of named variables in this scope. The client can use this optional information to present the variables in a paged UI and fetch them in chunks.

  • indexedVariablesScope :: Maybe Int

    The number of indexed variables in this scope. The client can use this optional information to present the variables in a paged UI and fetch them in chunks.

  • expensiveScope :: Bool

    If true, the number of variables in this scope is large or expensive to retrieve.

Instances
Eq Scope Source # 
Instance details

Defined in Haskell.DAP

Methods

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

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

Read Scope Source # 
Instance details

Defined in Haskell.DAP

Show Scope Source # 
Instance details

Defined in Haskell.DAP

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

data ScopesResponse Source #

Response to "scopes" request.

Constructors

ScopesResponse 

Fields

data ScopesResponseBody Source #

Response to scopes request.

Constructors

ScopesResponseBody 

Fields

variables

data VariablesRequest Source #

Variables request; value of command field is "variables".

Retrieves all children for the given variable reference.

Constructors

VariablesRequest 

Fields

data Variable Source #

A Variable is a name/value pair.

If the value is structured (has children), a handle is provided to retrieve the children with the VariablesRequest.

Constructors

Variable 

Fields

Instances
Eq Variable Source # 
Instance details

Defined in Haskell.DAP

Read Variable Source # 
Instance details

Defined in Haskell.DAP

Show Variable Source # 
Instance details

Defined in Haskell.DAP

data VariablePresentationHint Source #

Optional properties of a variable that can be used to determine how to render the variable in the UI.

Constructors

VariablePresentationHint 

Fields

  • kindVariablePresentationHint :: String

    The kind of variable. Before introducing additional values, try to use the listed values.

    Values:

    property: Indicates that the object is a property.

    method: Indicates that the object is a method.

    'class': Indicates that the object is a class.

    'data': Indicates that the object is data.

    event: Indicates that the object is an event.

    baseClass: Indicates that the object is a base class.

    innerClass: Indicates that the object is an inner class.

    interface: Indicates that the object is an interface.

    mostDerivedClass: Indicates that the object is the most derived class.

    virtual: Indicates that the object is virtual, that means it is a synthetic object introduced by the adapter for rendering purposes, e.g. an index range for large arrays.

  • attributesVariablePresentationHint :: [String]

    Set of attributes represented as an array of strings. Before introducing additional values, try to use the listed values. Values:

    static: Indicates that the object is static.

    constant: Indicates that the object is a constant.

    readOnly: Indicates that the object is read only.

    rawString: Indicates that the object is a raw string.

    hasObjectId: Indicates that the object can have an Object ID created for it.

    canHaveObjectId: Indicates that the object has an Object ID associated with it.

    hasSideEffects: Indicates that the evaluation had side effects.

  • visibilityVariablePresentationHint :: String

    Visibility of variable. Before introducing additional values, try to use the listed values.

    Values: public, private, protected, internal, final, etc.

data VariablesResponse Source #

Response to "variables" request.

Constructors

VariablesResponse 

Fields

continue

data ContinueRequest Source #

Continue request; value of command field is "continue".

The request starts the debuggee to run again.

Constructors

ContinueRequest 

Fields

data ContinueRequestArguments Source #

Arguments for continue request.

Constructors

ContinueRequestArguments 

Fields

data ContinueResponse Source #

Response to "continue" request. This is just an acknowledgement, so no body field is required.

Constructors

ContinueResponse 

Fields

next

data NextRequest Source #

Next request; value of command field is "next".

The request starts the debuggee to run again for one step.

penDebug will respond with a StoppedEvent (event type step) after running the step.

Constructors

NextRequest 

Fields

data NextResponse Source #

Response to "next" request. This is just an acknowledgement, so no body field is required.

Constructors

NextResponse 

Fields

stepIn

data StepInRequest Source #

StepIn request; value of command field is "stepIn".

The request starts the debuggee to run again for one step.

The debug adapter will respond with a StoppedEvent (event type step) after running the step.

Constructors

StepInRequest 

Fields

data StepInResponse Source #

Response to "stepIn" request. This is just an acknowledgement, so no body field is required.

Constructors

StepInResponse 

Fields

evaluate

data EvaluateRequest Source #

Evaluate request; value of command field is "evaluate".

Evaluates the given expression in the context of the top most stack frame.

The expression has access to any variables and arguments that are in scope.

Constructors

EvaluateRequest 

Fields

data EvaluateRequestArguments Source #

rguments for evaluate request.

Constructors

EvaluateRequestArguments 

Fields

data EvaluateResponse Source #

Response to "evaluate" request.

Constructors

EvaluateResponse 

Fields

data EvaluateResponseBody Source #

Response to "evaluate" request.

Constructors

EvaluateResponseBody 

Fields

completions

data CompletionsRequest Source #

CompletionsRequest request; value of command field is completions.

Returns a list of possible completions for a given caret position and text.

The CompletionsRequest may only be called if the supportsCompletionsRequest capability exists and is true.

Constructors

CompletionsRequest 

Fields

data CompletionsRequestArguments Source #

Arguments for completions request.

Constructors

CompletionsRequestArguments 

Fields

data CompletionsItem Source #

CompletionItems are the suggestions returned from the CompletionsRequest.

Constructors

CompletionsItem 

Fields

  • labelCompletionsItem :: String

    The label of this completion item. By default this is also the text that is inserted when selecting this completion.

data CompletionsResponse Source #

Response to completions request.

Constructors

CompletionsResponse 

Fields

event

data OutputEvent Source #

Event message for "output" event type. The event indicates that the target has produced output.

Constructors

OutputEvent 

Fields

data OutputEventBody Source #

Event message for "output" event type. The event indicates that the target has produced output.

Constructors

OutputEventBody 

Fields

data InitializedEvent Source #

Server-initiated response to client request

Constructors

InitializedEvent 

Fields

data TerminatedEvent Source #

Event message for "terminated" event types.

The event indicates that debugging of the debuggee has terminated.

Constructors

TerminatedEvent 

Fields

data TerminatedEventBody Source #

Event message for "terminated" event types.

The event indicates that debugging of the debuggee has terminated.

Constructors

TerminatedEventBody 

Fields

data ExitedEvent Source #

Event message for "exited" event types.

Constructors

ExitedEvent 

Fields

data ExitedEventBody Source #

Event message for "exited" event types.

The exit code returned from the debuggee.

data ContinuedEvent Source #

Event message for continued event type.

The event indicates that the execution of the debuggee has continued.

Please note: a debug adapter is not expected to send this event in response to a request that implies that execution continues, e.g. launch or continue.

It is only necessary to send a continued event if there was no previous request that implied this.

Constructors

ContinuedEvent 

Fields

data ContinuedEventBody Source #

Body of ContinuedEvent

Constructors

ContinuedEventBody 

Fields

data StoppedEvent Source #

Event message for "stopped" event type.

The event indicates that the execution of the debuggee has stopped due to some condition.

This can be caused by a break point previously set, a stepping action has completed, by executing a debugger statement etc.

Constructors

StoppedEvent 

Fields

data StoppedEventBody Source #

Event message for stopped event type.

The event indicates that the execution of the debuggee has stopped due to some condition.

This can be caused by a break point previously set, a stepping action has completed, by executing a debugger statement etc.

Constructors

StoppedEventBody 

Fields

  • reasonStoppedEventBody :: String

    The reason for the event.For backward compatibility this string is shown in the UI if the description attribute is missing (but it must not be translated).Values: step, breakpoint, exception, pause, entry, etc.

  • descriptionStoppedEventBody :: String

    The full reason for the event, e.g. 'Paused on exception'. This string is shown in the UI as is.

  • threadIdStoppedEventBody :: Int

    The thread which was stopped.

  • textStoppedEventBody :: String

    Additional information. E.g. if reason is exception, text contains the exception name. This string is shown in the UI.

  • allThreadsStoppedStoppedEventBody :: Bool

    If allThreadsStopped is true, a debug adapter can announce that all threads have stopped. The client should use this information to enable that all threads can be expanded to access their stacktraces. If the attribute is missing or false, only the thread with the given threadId can be expanded.