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

Copyright2017-2018 phoityne_hs
LicenseBSD3
Safe HaskellSafe
LanguageHaskell2010

GHCi.DAP.IFData

Contents

Description

This module will be deprecated.

@see : Haskell.DAP module.

Implementation of DAP interface data type.

@see : https://github.com/Microsoft/vscode-debugadapter-node/blob/master/protocol/src/debugProtocol.ts

Synopsis

setBreakpoints

data SourceBreakpoint Source #

Properties of a breakpoint passed to the setBreakpoints request.

Constructors

SourceBreakpoint 

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

Constructors

SetBreakpointsResponseBody 

Fields

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.

setFunctionBreakpoints

continue

data ContinueArguments Source #

Arguments for continue request.

Constructors

ContinueArguments 

Fields

  • threadIdContinueArguments :: Int

    Continue execution for the specified thread (if possible). If the backend cannot continue on a single thread but will continue on all threads, it should set the allThreadsContinued attribute in the response to true.

  • exprContinueArguments :: Maybe String

    ADD: haskell-dap

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.

next

stepIn

scopes

data ScopesArguments Source #

Arguments for "scopes" request.

Constructors

ScopesArguments 

Fields

data ScopesBody Source #

Response to scopes request.

Constructors

ScopesBody 

Fields

  • scopesScopesBody :: [Scope]

    The scopes of the stackframe. If the array has length zero, there are no scopes available.

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 GHCi.DAP.IFData

Methods

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

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

Read Scope Source # 
Instance details

Defined in GHCi.DAP.IFData

Show Scope Source # 
Instance details

Defined in GHCi.DAP.IFData

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

stackTrace

data StackTraceArguments Source #

Arguments for stackTrace request.

Constructors

StackTraceArguments 

Fields

data StackTraceBody Source #

Response to stackTrace request.

Constructors

StackTraceBody 

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.

variables

data VariablesBody Source #

Response to "variables" request.

Constructors

VariablesBody 

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 GHCi.DAP.IFData

Read Variable Source # 
Instance details

Defined in GHCi.DAP.IFData

Show Variable Source # 
Instance details

Defined in GHCi.DAP.IFData

evaluate

data EvaluateArguments Source #

rguments for evaluate request.

Constructors

EvaluateArguments 

Fields

data EvaluateBody Source #

Response to "evaluate" request.

Constructors

EvaluateBody 

Fields

event

data OutputEventBody Source #

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

Constructors

OutputEventBody 

Fields

commons

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 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 GHCi.DAP.IFData

Methods

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

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

Read Source Source # 
Instance details

Defined in GHCi.DAP.IFData

Show Source Source # 
Instance details

Defined in GHCi.DAP.IFData