dap-0.1.0.0: A debug adaptor protocol library
Safe HaskellSafe-Inferred
LanguageHaskell2010

DAP

Synopsis

Message Construction

setBody :: ToJSON value => value -> Adaptor app () Source #

setField :: ToJSON value => Key -> value -> Adaptor app () Source #

Response

sendErrorResponse :: ErrorMessage -> Maybe Message -> Adaptor app () Source #

Sends unsuccessful response Only used internally within the Server module

Events

sendSuccesfulEvent :: EventType -> Adaptor app () -> Adaptor app () Source #

Sends successful event

Server

Request Arguments

getArguments :: (Show value, FromJSON value) => Adaptor app value Source #

Attempt to parse arguments from the Request

Debug Session

registerNewDebugSession Source #

Arguments

:: SessionId 
-> app 
-> IO ()

Action to run debugger (operates in a forked thread that gets killed when disconnect is set)

-> ((Adaptor app () -> IO ()) -> IO ())

Long running operation, meant to be used as a sink for the debugger to emit events and for the adaptor to forward to the editor This function should be in a forever loop waiting on the read end of a debugger channel.

This event handler thread also takes an argument that allows any child thread to execute events on behalf of the DAP server (in 'Adaptor app ()'). This function should always be used when sending events to the editor from the debugger (or from any forked thread).

registerNewDebugSession sessionId appState loadDebugger $ \withAdaptor ->
  forever $ getDebuggerOutput >>= \output -> do
    withAdaptor $ sendOutputEvent defaultOutputEvent { outputEventOutput = output }
-> Adaptor app () 

updateDebugSession :: (app -> app) -> Adaptor app () Source #

destroyDebugSession :: Adaptor app () Source #

Whenever a debug Session ends (cleanly or otherwise) this function will remove the local debugger communication state from the global state

Error handling

sendError :: ErrorMessage -> Maybe Message -> Adaptor app a Source #

Raises an error Meant abort the current reqeust / response cycle, prematurely sending an ErrorResponse https://microsoft.github.io/debug-adapter-protocol/specification#Base_Protocol_ErrorResponse

Logging

logger :: Level -> SockAddr -> Maybe DebugStatus -> ByteString -> IO () Source #

Meant for external consumption

debugMessage :: ByteString -> Adaptor app () Source #

Meant for internal consumption, used to signify a message has been SENT from the server

Internal use

send :: Adaptor app () -> Adaptor app () Source #

Function for constructing a payload and writing bytes to a socket. This function takes care of incrementing sequence numbers and setting fields automatically that are required for response messages. i.e. "request_seq" and "command". We also have to be sure to reset the message payload

sendRaw :: ToJSON value => value -> Adaptor app () Source #

sendRaw (internal use only) Sends a raw JSON payload to the editor. No "seq", "type" or "command" fields are set. The message is still encoded with the ProtocolMessage Header, byte count, and CRLF.

Internal function used to execute actions on behalf of the DAP server

runAdaptorWith :: MVar (AdaptorState app) -> Adaptor app () -> IO () Source #

Evaluates Adaptor action by using and updating the state in the MVar

Event message API

Defaults

withLock :: MVar () -> IO () -> IO () Source #

Used for performing actions (e.g. printing debug logs to stdout) Also used for writing to each connections Handle. Ensures operations occur one thread at a time.

Used internally only

withGlobalLock :: IO () -> IO () Source #

Used for performing actions (e.g. printing debug logs to stdout) Ensures operations occur one thread at a time.

Used internally only

Response message API

sendAttachResponse :: Adaptor app () Source #

AttachResponse has no body by default

sendBreakpointLocationsResponse :: [BreakpointLocation] -> Adaptor app () Source #

BreakpointLocationResponse has no body by default

sendConfigurationDoneResponse :: Adaptor app () Source #

ConfigurationDoneResponse

sendDisconnectResponse :: Adaptor app () Source #

DisconnectResponse

sendGotoResponse :: Adaptor app () Source #

GotoResponse

sendGotoTargetsResponse :: Adaptor app () Source #

GotoTargetsResponse

sendInitializeResponse :: Adaptor app () Source #

InitializeReponse

sendLaunchResponse :: Adaptor app () Source #

LaunchResponse

sendNextResponse :: Adaptor app () Source #

NextResponse

sendPauseResponse :: Adaptor app () Source #

PauseResponse

sendRestartResponse :: Adaptor app () Source #

RestartResponse

sendRestartFrameResponse :: Adaptor app () Source #

RestartFrameResponse

sendReverseContinueResponse :: Adaptor app () Source #

ReverseContinueResponse

sendSetBreakpointsResponse :: [Breakpoint] -> Adaptor app () Source #

BreakpointResponse has no body by default

sendSetDataBreakpointsResponse :: [Breakpoint] -> Adaptor app () Source #

SetDataBreakpointsResponse

sendSetExceptionBreakpointsResponse :: [Breakpoint] -> Adaptor app () Source #

SetExceptionBreakpointsResponse has no body by default

sendSetFunctionBreakpointsResponse :: [Breakpoint] -> Adaptor app () Source #

SetFunctionBreakpointResponse has no body by default

sendSetInstructionBreakpointsResponse :: [Breakpoint] -> Adaptor app () Source #

SetInstructionsBreakpointResponse has no body by default

sendStepBackResponse :: Adaptor app () Source #

StepBackResponse

sendStepInResponse :: Adaptor app () Source #

StepInResponse

sendStepOutResponse :: Adaptor app () Source #

StepOutResponse

sendTerminateResponse :: Adaptor app () Source #

TerminateResponse

sendTerminateThreadsResponse :: Adaptor app () Source #

TerminateThreadsResponse

runDAPServer Source #

Arguments

:: ServerConfig

Top-level Server configuration, global across all debug sessions

-> (Command -> Adaptor app ())

A function to facilitate communication between DAP clients, debug adaptors and debuggers

-> IO () 

readPayload :: FromJSON json => Handle -> IO (Either String json) Source #

Helper function to parse a ProtocolMessage, extracting it's body. used for testing.

Message Type

data MessageType Source #

Instances

Instances details
ToJSON MessageType Source # 
Instance details

Defined in DAP.Types

Generic MessageType Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep MessageType :: Type -> Type Source #

Show MessageType Source # 
Instance details

Defined in DAP.Types

Eq MessageType Source # 
Instance details

Defined in DAP.Types

type Rep MessageType Source # 
Instance details

Defined in DAP.Types

type Rep MessageType = D1 ('MetaData "MessageType" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "MessageTypeEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MessageTypeResponse" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MessageTypeRequest" 'PrefixI 'False) (U1 :: Type -> Type)))

Types

data Breakpoint Source #

Constructors

Breakpoint 

Fields

Instances

Instances details
ToJSON Breakpoint Source # 
Instance details

Defined in DAP.Types

Generic Breakpoint Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep Breakpoint :: Type -> Type Source #

Show Breakpoint Source # 
Instance details

Defined in DAP.Types

Eq Breakpoint Source # 
Instance details

Defined in DAP.Types

type Rep Breakpoint Source # 
Instance details

Defined in DAP.Types

newtype Breakpoints breakpoint Source #

Constructors

Breakpoints [breakpoint] 

Instances

Instances details
ToJSON breakpoint => ToJSON (Breakpoints breakpoint) Source # 
Instance details

Defined in DAP.Types

Methods

toJSON :: Breakpoints breakpoint -> Value Source #

toEncoding :: Breakpoints breakpoint -> Encoding Source #

toJSONList :: [Breakpoints breakpoint] -> Value Source #

toEncodingList :: [Breakpoints breakpoint] -> Encoding Source #

Show breakpoint => Show (Breakpoints breakpoint) Source # 
Instance details

Defined in DAP.Types

Methods

showsPrec :: Int -> Breakpoints breakpoint -> ShowS Source #

show :: Breakpoints breakpoint -> String Source #

showList :: [Breakpoints breakpoint] -> ShowS Source #

Eq breakpoint => Eq (Breakpoints breakpoint) Source # 
Instance details

Defined in DAP.Types

Methods

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

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

data BreakpointLocation Source #

Constructors

BreakpointLocation 

Fields

Instances

Instances details
ToJSON BreakpointLocation Source # 
Instance details

Defined in DAP.Types

Generic BreakpointLocation Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep BreakpointLocation :: Type -> Type Source #

Show BreakpointLocation Source # 
Instance details

Defined in DAP.Types

Eq BreakpointLocation Source # 
Instance details

Defined in DAP.Types

type Rep BreakpointLocation Source # 
Instance details

Defined in DAP.Types

type Rep BreakpointLocation = D1 ('MetaData "BreakpointLocation" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "BreakpointLocation" 'PrefixI 'True) ((S1 ('MetaSel ('Just "breakpointLocationLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "breakpointLocationColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "breakpointLocationEndLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "breakpointLocationEndColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))

data Capabilities Source #

Constructors

Capabilities 

Fields

Instances

Instances details
ToJSON Capabilities Source # 
Instance details

Defined in DAP.Types

Generic Capabilities Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep Capabilities :: Type -> Type Source #

Show Capabilities Source # 
Instance details

Defined in DAP.Types

Eq Capabilities Source # 
Instance details

Defined in DAP.Types

type Rep Capabilities Source # 
Instance details

Defined in DAP.Types

type Rep Capabilities = D1 ('MetaData "Capabilities" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "Capabilities" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "supportsConfigurationDoneRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsFunctionBreakpoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "supportsConditionalBreakpoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsHitConditionalBreakpoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "supportsEvaluateForHovers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "exceptionBreakpointFilters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExceptionBreakpointsFilter])) :*: (S1 ('MetaSel ('Just "supportsStepBack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "supportsSetVariable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsRestartFrame") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) :*: (((S1 ('MetaSel ('Just "supportsGotoTargetsRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsStepInTargetsRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "supportsCompletionsRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "completionTriggerCharacters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "supportsModulesRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "additionalModuleColumns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ColumnDescriptor]) :*: S1 ('MetaSel ('Just "supportedChecksumAlgorithms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ChecksumAlgorithm])) :*: (S1 ('MetaSel ('Just "supportsRestartRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "supportsExceptionOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsValueFormattingOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))) :*: ((((S1 ('MetaSel ('Just "supportsExceptionInfoRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportTerminateDebuggee") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "supportSuspendDebuggee") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "supportsDelayedStackTraceLoading") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsLoadedSourcesRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "supportsLogPoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsTerminateThreadsRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "supportsSetExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "supportsTerminateRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsDataBreakpoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) :*: (((S1 ('MetaSel ('Just "supportsReadMemoryRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsWriteMemoryRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "supportsDisassembleRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "supportsCancelRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsBreakpointLocationsRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "supportsClipboardContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsSteppingGranularity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "supportsInstructionBreakpoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "supportsExceptionFilterOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsSingleThreadExecutionRequests") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))))))

data Checksum Source #

Constructors

Checksum 

Fields

Instances

Instances details
FromJSON Checksum Source # 
Instance details

Defined in DAP.Types

ToJSON Checksum Source # 
Instance details

Defined in DAP.Types

Generic Checksum Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep Checksum :: Type -> Type Source #

Show Checksum Source # 
Instance details

Defined in DAP.Types

Eq Checksum Source # 
Instance details

Defined in DAP.Types

type Rep Checksum Source # 
Instance details

Defined in DAP.Types

type Rep Checksum = D1 ('MetaData "Checksum" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "Checksum" 'PrefixI 'True) (S1 ('MetaSel ('Just "algorithm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChecksumAlgorithm) :*: S1 ('MetaSel ('Just "checksum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data ColumnDescriptor Source #

A ColumnDescriptor specifies what module attribute to show in a column of the modules view, 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

Instances

Instances details
ToJSON ColumnDescriptor Source # 
Instance details

Defined in DAP.Types

Generic ColumnDescriptor Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ColumnDescriptor :: Type -> Type Source #

Show ColumnDescriptor Source # 
Instance details

Defined in DAP.Types

Eq ColumnDescriptor Source # 
Instance details

Defined in DAP.Types

type Rep ColumnDescriptor Source # 
Instance details

Defined in DAP.Types

type Rep ColumnDescriptor = D1 ('MetaData "ColumnDescriptor" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ColumnDescriptor" 'PrefixI 'True) ((S1 ('MetaSel ('Just "columnDescriptorAttributeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "columnDescriptorLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "columnDescriptorFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Just "columnDescriptorType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ColumnDescriptorType)) :*: S1 ('MetaSel ('Just "columnDescriptorWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))))

data CompletionItem Source #

Constructors

CompletionItem 

Fields

  • completionItemLabel :: String

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

  • completionItemText :: Maybe String

    If text is returned and not an empty string, then it is inserted instead of the label.

  • completionItemSortText :: Maybe String

    A string that should be used when comparing this item with other items. If not returned or an empty string, the label is used instead.

  • completionItemDetail :: Maybe String

    A human-readable string with additional information about this item, like type or symbol information.

  • completionItemType :: Maybe CompletionItemType

    The item's type. Typically the client uses this information to render the item in the UI with an icon.

  • completionItemTypeStart :: Maybe Int

    Start position (within the text attribute of the completions request) where the completion text is added. The position is measured in UTF-16 code units and the client capability columnsStartAt1 determines whether it is 0- or 1-based. If the start position is omitted the text is added at the location specified by the column attribute of the completions request.

  • completionItemTypeLength :: Maybe Int

    Length determines how many characters are overwritten by the completion text and it is measured in UTF-16 code units. If missing the value 0 is assumed which results in the completion text being inserted.

  • completionItemTypeSelectionStart :: Maybe Int

    Determines the start of the new selection after the text has been inserted (or replaced). selectionStart is measured in UTF-16 code units and must be in the range 0 and length of the completion text. If omitted the selection starts at the end of the completion text.

  • completionItemTypeSelectionLength :: Maybe Int

    Determines the length of the new selection after the text has been inserted (or replaced) and it is measured in UTF-16 code units. The selection can not extend beyond the bounds of the completion text. If omitted the length is assumed to be 0.

Instances

Instances details
ToJSON CompletionItem Source # 
Instance details

Defined in DAP.Types

Generic CompletionItem Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep CompletionItem :: Type -> Type Source #

Show CompletionItem Source # 
Instance details

Defined in DAP.Types

Eq CompletionItem Source # 
Instance details

Defined in DAP.Types

type Rep CompletionItem Source # 
Instance details

Defined in DAP.Types

type Rep CompletionItem = D1 ('MetaData "CompletionItem" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "CompletionItem" 'PrefixI 'True) (((S1 ('MetaSel ('Just "completionItemLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "completionItemText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :*: (S1 ('MetaSel ('Just "completionItemSortText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "completionItemDetail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))) :*: ((S1 ('MetaSel ('Just "completionItemType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CompletionItemType)) :*: S1 ('MetaSel ('Just "completionItemTypeStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "completionItemTypeLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "completionItemTypeSelectionStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "completionItemTypeSelectionLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))))

data CompletionItemType Source #

Instances

Instances details
ToJSON CompletionItemType Source # 
Instance details

Defined in DAP.Types

Generic CompletionItemType Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep CompletionItemType :: Type -> Type Source #

Show CompletionItemType Source # 
Instance details

Defined in DAP.Types

Eq CompletionItemType Source # 
Instance details

Defined in DAP.Types

type Rep CompletionItemType Source # 
Instance details

Defined in DAP.Types

type Rep CompletionItemType = D1 ('MetaData "CompletionItemType" "DAP.Types" "dap-0.1.0.0-inplace" 'False) ((((C1 ('MetaCons "CompletionItemTypeMethod" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CompletionItemTypeFunction" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CompletionItemTypeConstructor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CompletionItemTypeField" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CompletionItemTypeVariable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CompletionItemTypeClass" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CompletionItemTypeInterface" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CompletionItemTypeModule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CompletionItemTypeProperty" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CompletionItemTypeUnit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CompletionItemTypeValue" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CompletionItemTypeEnum" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CompletionItemTypeKeyword" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CompletionItemTypeSnippet" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CompletionItemTypeText" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CompletionItemTypeColor" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CompletionItemTypeFile" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CompletionItemTypeReference" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CompletionItemTypeCustomcolor" 'PrefixI 'False) (U1 :: Type -> Type))))))

data DataBreakpoint Source #

Constructors

DataBreakpoint 

Fields

Instances

Instances details
FromJSON DataBreakpoint Source # 
Instance details

Defined in DAP.Types

Generic DataBreakpoint Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep DataBreakpoint :: Type -> Type Source #

Show DataBreakpoint Source # 
Instance details

Defined in DAP.Types

Eq DataBreakpoint Source # 
Instance details

Defined in DAP.Types

type Rep DataBreakpoint Source # 
Instance details

Defined in DAP.Types

type Rep DataBreakpoint = D1 ('MetaData "DataBreakpoint" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "DataBreakpoint" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dataBreakpointDataId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "dataBreakpointAccessType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DataBreakpointAccessType))) :*: (S1 ('MetaSel ('Just "condition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "hitCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

data DataBreakpointAccessType Source #

This enumeration defines all possible access types for data breakpoints. Values: ‘read’, ‘write’, ‘readWrite’

Instances

Instances details
FromJSON DataBreakpointAccessType Source # 
Instance details

Defined in DAP.Types

ToJSON DataBreakpointAccessType Source #

type DataBreakpointAccessType = read | write | readWrite;

Instance details

Defined in DAP.Types

Generic DataBreakpointAccessType Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep DataBreakpointAccessType :: Type -> Type Source #

Show DataBreakpointAccessType Source # 
Instance details

Defined in DAP.Types

Eq DataBreakpointAccessType Source # 
Instance details

Defined in DAP.Types

type Rep DataBreakpointAccessType Source # 
Instance details

Defined in DAP.Types

type Rep DataBreakpointAccessType = D1 ('MetaData "DataBreakpointAccessType" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "DataBreakpointAccessTypeRead" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DataBreakpointAccessTypeWrite" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataBreakpointAccessTypeReadWrite" 'PrefixI 'False) (U1 :: Type -> Type)))

data DisassembledInstruction Source #

Constructors

DisassembledInstruction 

Fields

Instances

Instances details
ToJSON DisassembledInstruction Source # 
Instance details

Defined in DAP.Types

Generic DisassembledInstruction Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep DisassembledInstruction :: Type -> Type Source #

Show DisassembledInstruction Source # 
Instance details

Defined in DAP.Types

Eq DisassembledInstruction Source # 
Instance details

Defined in DAP.Types

type Rep DisassembledInstruction Source # 
Instance details

Defined in DAP.Types

type Rep DisassembledInstruction = D1 ('MetaData "DisassembledInstruction" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "DisassembledInstruction" 'PrefixI 'True) (((S1 ('MetaSel ('Just "disassembledInstructionAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "disassembledInstructionInstructionBytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "disassembledInstructionInstruction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "disassembledInstructionSymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: ((S1 ('MetaSel ('Just "disassembledInstructionLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Source)) :*: S1 ('MetaSel ('Just "disassembledInstructionLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "disassembledInstructionColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "disassembledInstructionEndLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "disassembledInstructionEndColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))))

data ExceptionBreakMode Source #

Instances

Instances details
FromJSON ExceptionBreakMode Source # 
Instance details

Defined in DAP.Types

ToJSON ExceptionBreakMode Source # 
Instance details

Defined in DAP.Types

Generic ExceptionBreakMode Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ExceptionBreakMode :: Type -> Type Source #

Show ExceptionBreakMode Source # 
Instance details

Defined in DAP.Types

Eq ExceptionBreakMode Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionBreakMode Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionBreakMode = D1 ('MetaData "ExceptionBreakMode" "DAP.Types" "dap-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "Never" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Always" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Unhandled" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UserUnhandled" 'PrefixI 'False) (U1 :: Type -> Type)))

data ExceptionBreakpointsFilter Source #

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

Constructors

ExceptionBreakpointsFilter 

Fields

Instances

Instances details
ToJSON ExceptionBreakpointsFilter Source # 
Instance details

Defined in DAP.Types

Generic ExceptionBreakpointsFilter Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ExceptionBreakpointsFilter :: Type -> Type Source #

Show ExceptionBreakpointsFilter Source # 
Instance details

Defined in DAP.Types

Eq ExceptionBreakpointsFilter Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionBreakpointsFilter Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionBreakpointsFilter = D1 ('MetaData "ExceptionBreakpointsFilter" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ExceptionBreakpointsFilter" 'PrefixI 'True) ((S1 ('MetaSel ('Just "exceptionBreakpointsFilterFilter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "exceptionBreakpointsFilterLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "exceptionBreakpointsFilterDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: (S1 ('MetaSel ('Just "exceptionBreakpointsFilterDefault") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "exceptionBreakpointsFilterSupportsCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "exceptionBreakpointsFilterConditionDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))))

data ExceptionDetails Source #

Constructors

ExceptionDetails 

Fields

Instances

Instances details
ToJSON ExceptionDetails Source # 
Instance details

Defined in DAP.Types

Generic ExceptionDetails Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ExceptionDetails :: Type -> Type Source #

Show ExceptionDetails Source # 
Instance details

Defined in DAP.Types

Eq ExceptionDetails Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionDetails Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionDetails = D1 ('MetaData "ExceptionDetails" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ExceptionDetails" 'PrefixI 'True) ((S1 ('MetaSel ('Just "exceptionDetailsMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Just "exceptionDetailstypeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "exceptionDetailsFullTypeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: (S1 ('MetaSel ('Just "exceptionDetailsEvaluateName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "exceptionDetailsStackTrace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "exceptionDetailsInnerException") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [ExceptionDetails]))))))

data ExceptionFilterOptions Source #

Constructors

ExceptionFilterOptions 

Fields

Instances

Instances details
FromJSON ExceptionFilterOptions Source # 
Instance details

Defined in DAP.Types

Generic ExceptionFilterOptions Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ExceptionFilterOptions :: Type -> Type Source #

Show ExceptionFilterOptions Source # 
Instance details

Defined in DAP.Types

Eq ExceptionFilterOptions Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionFilterOptions Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionFilterOptions = D1 ('MetaData "ExceptionFilterOptions" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ExceptionFilterOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "exceptionFilterOptionsFilterId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "exceptionFilterOptionsCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))

data ExceptionOptions Source #

Constructors

ExceptionOptions 

Fields

Instances

Instances details
FromJSON ExceptionOptions Source # 
Instance details

Defined in DAP.Types

Generic ExceptionOptions Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ExceptionOptions :: Type -> Type Source #

Show ExceptionOptions Source # 
Instance details

Defined in DAP.Types

Eq ExceptionOptions Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionOptions Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionOptions = D1 ('MetaData "ExceptionOptions" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ExceptionOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "exceptionOptionsPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [ExceptionPathSegment])) :*: S1 ('MetaSel ('Just "exceptionOptionsBreakMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExceptionBreakMode)))

data ExceptionPathSegment Source #

An ExceptionPathSegment represents a segment in a path that is used to match leafs or nodes in a tree of exceptions. If a segment consists of more than one name, it matches the names provided if negate is false or missing, or it matches anything except the names provided if negate is true.

data FunctionBreakpoint Source #

Constructors

FunctionBreakpoint 

Fields

Instances

Instances details
FromJSON FunctionBreakpoint Source # 
Instance details

Defined in DAP.Types

Generic FunctionBreakpoint Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep FunctionBreakpoint :: Type -> Type Source #

Show FunctionBreakpoint Source # 
Instance details

Defined in DAP.Types

Eq FunctionBreakpoint Source # 
Instance details

Defined in DAP.Types

type Rep FunctionBreakpoint Source # 
Instance details

Defined in DAP.Types

type Rep FunctionBreakpoint = D1 ('MetaData "FunctionBreakpoint" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "FunctionBreakpoint" 'PrefixI 'True) (S1 ('MetaSel ('Just "functionBreakpointName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "functionBreakpointCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "functionBreakpointHitCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

data GotoTarget Source #

Constructors

GotoTarget 

Fields

Instances

Instances details
ToJSON GotoTarget Source # 
Instance details

Defined in DAP.Types

Generic GotoTarget Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep GotoTarget :: Type -> Type Source #

Show GotoTarget Source # 
Instance details

Defined in DAP.Types

Eq GotoTarget Source # 
Instance details

Defined in DAP.Types

type Rep GotoTarget Source # 
Instance details

Defined in DAP.Types

type Rep GotoTarget = D1 ('MetaData "GotoTarget" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "GotoTarget" 'PrefixI 'True) ((S1 ('MetaSel ('Just "gotoTargetId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "gotoTargetLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "gotoTargetLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "gotoTargetColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "gotoTargetEndLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "gotoTargetEndColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "gotoTargetInstructionPointerReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))))

data InstructionBreakpoint Source #

Constructors

InstructionBreakpoint 

Fields

Instances

Instances details
FromJSON InstructionBreakpoint Source # 
Instance details

Defined in DAP.Types

Generic InstructionBreakpoint Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep InstructionBreakpoint :: Type -> Type Source #

Show InstructionBreakpoint Source # 
Instance details

Defined in DAP.Types

Eq InstructionBreakpoint Source # 
Instance details

Defined in DAP.Types

type Rep InstructionBreakpoint Source # 
Instance details

Defined in DAP.Types

type Rep InstructionBreakpoint = D1 ('MetaData "InstructionBreakpoint" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "InstructionBreakpoint" 'PrefixI 'True) ((S1 ('MetaSel ('Just "instructionBreakpointInstructionReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "instructionBreakpointOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "instructionBreakpointCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "instructionBreakpointHitCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

data InvalidatedAreas Source #

Logical areas that can be invalidated by the invalidated event. Values: https://microsoft.github.io/debug-adapter-protocol/specification#Types_InvalidatedAreas

Instances

Instances details
ToJSON InvalidatedAreas Source # 
Instance details

Defined in DAP.Types

Generic InvalidatedAreas Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep InvalidatedAreas :: Type -> Type Source #

Show InvalidatedAreas Source # 
Instance details

Defined in DAP.Types

Eq InvalidatedAreas Source # 
Instance details

Defined in DAP.Types

type Rep InvalidatedAreas Source # 
Instance details

Defined in DAP.Types

type Rep InvalidatedAreas = D1 ('MetaData "InvalidatedAreas" "DAP.Types" "dap-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "InvalidatedAreasAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidatedAreasStacks" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "InvalidatedAreasThreads" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidatedAreasVariables" 'PrefixI 'False) (U1 :: Type -> Type)))

data Message Source #

Constructors

Message 

Fields

  • messageId :: Int

    Unique (within a debug adapter implementation) identifier for the message. The purpose of these error IDs is to help extension authors that have the requirement that every user visible error message needs a corresponding error number, so that users or customer support can find information about the specific error more easily.

  • messageFormat :: Text

    A format string for the message. Embedded variables have the form `{name}`. If variable name starts with an underscore character, the variable does not contain user data (PII) and can be safely used for telemetry purposes.

  • messageVariables :: Maybe (HashMap Text Text)

    An object used as a dictionary for looking up the variables in the format string.

  • messageSendTelemetry :: Maybe Bool

    If true send to telemetry.

  • messageShowUser :: Maybe Bool

    If true show user.

  • messageUrl :: Maybe Text

    A url where additional information about this message can be found.

  • messageUrlLabel :: Maybe Text

    A label that is presented to the user as the UI for opening the url.

Instances

Instances details
ToJSON Message Source # 
Instance details

Defined in DAP.Types

Generic Message Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep Message :: Type -> Type Source #

Show Message Source # 
Instance details

Defined in DAP.Types

Eq Message Source # 
Instance details

Defined in DAP.Types

MonadError (ErrorMessage, Maybe Message) (Adaptor store) Source # 
Instance details

Defined in DAP.Types

Methods

throwError :: (ErrorMessage, Maybe Message) -> Adaptor store a Source #

catchError :: Adaptor store a -> ((ErrorMessage, Maybe Message) -> Adaptor store a) -> Adaptor store a Source #

type Rep Message Source # 
Instance details

Defined in DAP.Types

data Module Source #

Constructors

Module 

Fields

Instances

Instances details
ToJSON Module Source # 
Instance details

Defined in DAP.Types

Generic Module Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep Module :: Type -> Type Source #

Show Module Source # 
Instance details

Defined in DAP.Types

Eq Module Source # 
Instance details

Defined in DAP.Types

type Rep Module Source # 
Instance details

Defined in DAP.Types

data ModulesViewDescriptor Source #

data PresentationHint Source #

Instances

Instances details
ToJSON PresentationHint Source # 
Instance details

Defined in DAP.Types

Generic PresentationHint Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep PresentationHint :: Type -> Type Source #

Show PresentationHint Source # 
Instance details

Defined in DAP.Types

Eq PresentationHint Source # 
Instance details

Defined in DAP.Types

type Rep PresentationHint Source # 
Instance details

Defined in DAP.Types

type Rep PresentationHint = D1 ('MetaData "PresentationHint" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "PresentationHintNormal" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PresentationHintLabel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PresentationHintSubtle" 'PrefixI 'False) (U1 :: Type -> Type)))

data Scope Source #

Constructors

Scope 

Fields

  • scopeName :: Text

    Name of the scope such as Arguments, Locals, or Registers. This string is shown in the UI as is and can be translated.

  • scopePresentationHint :: Maybe ScopePresentationHint

    A hint for how to present this scope in the UI. If this attribute is missing, the scope is shown with a generic UI. Values: arguments: Scope contains method arguments. locals: Scope contains local variables. registers: Scope contains registers. Only a single registers scope should be returned from a scopes request. etc.

  • scopeVariablesReference :: Int

    The variables of this scope can be retrieved by passing the value of variablesReference to the variables request as long as execution remains suspended. See 'Lifetime of Object References' in the Overview section for details.

  • scopeNamedVariables :: Maybe Int

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

  • scopeIndexedVariables :: Maybe Int

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

  • scopeExpensive :: Bool

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

  • scopeSource :: Maybe Source

    The source for this scope.

  • scopeLine :: Maybe Int

    The start line of the range covered by this scope.

  • scopeColumn :: Maybe Int

    Start position of the range covered by the scope. It is measured in UTF-16 code units and the client capability columnsStartAt1 determines whether it is 0- or 1-based.

  • scopeEndLine :: Maybe Int

    The end line of the range covered by this scope.

  • scopeEndColumn :: Maybe Int

    End position of the range covered by the scope. It is measured in UTF-16 code units and the client capability columnsStartAt1 determines whether it is 0- or 1-based.

Instances

Instances details
ToJSON Scope Source # 
Instance details

Defined in DAP.Types

Generic Scope Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep Scope :: Type -> Type Source #

Methods

from :: Scope -> Rep Scope x Source #

to :: Rep Scope x -> Scope Source #

Show Scope Source # 
Instance details

Defined in DAP.Types

Eq Scope Source # 
Instance details

Defined in DAP.Types

Methods

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

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

type Rep Scope Source # 
Instance details

Defined in DAP.Types

data Source Source #

Constructors

Source 

Fields

  • sourceName :: Maybe Text

    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.

  • sourcePath :: Maybe Text

    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 value is 0).

  • sourceSourceReference :: Maybe Int

    If the value > 0 the contents of the source must be retrieved through the source request (even if a path is specified). Since a sourceReference is only valid for a session, it can not be used to persist a source. The value should be less than or equal to 2147483647 (2^31-1).

  • sourcePresentationHint :: Maybe SourcePresentationHint

    A hint for how to present the source in the UI. A value of deemphasize can be used to indicate that the source is not available or that it is skipped on stepping. Values: normal, emphasize, deemphasize

  • sourceOrigin :: Maybe Text

    The origin of this source. For example, 'internal module', 'inlined content from source map', etc.

  • sourceSources :: Maybe [Source]

    A list of sources that are related to this source. These may be the source that generated this source.

  • sourceAdapterData :: Maybe Value

    Additional data that a debug adapter might want to loop through the client. The client should leave the data intact and persist it across sessions. The client should not interpret the data.

  • sourceChecksums :: Maybe [Checksum]

    The checksums associated with this file.

Instances

Instances details
FromJSON Source Source # 
Instance details

Defined in DAP.Types

ToJSON Source Source # 
Instance details

Defined in DAP.Types

Generic Source Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep Source :: Type -> Type Source #

Show Source Source # 
Instance details

Defined in DAP.Types

Eq Source Source # 
Instance details

Defined in DAP.Types

type Rep Source Source # 
Instance details

Defined in DAP.Types

data SourceBreakpoint Source #

Constructors

SourceBreakpoint 

Fields

Instances

Instances details
FromJSON SourceBreakpoint Source # 
Instance details

Defined in DAP.Types

Generic SourceBreakpoint Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep SourceBreakpoint :: Type -> Type Source #

Show SourceBreakpoint Source # 
Instance details

Defined in DAP.Types

Eq SourceBreakpoint Source # 
Instance details

Defined in DAP.Types

type Rep SourceBreakpoint Source # 
Instance details

Defined in DAP.Types

type Rep SourceBreakpoint = D1 ('MetaData "SourceBreakpoint" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SourceBreakpoint" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sourceBreakpointLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "sourceBreakpointColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "sourceBreakpointCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "sourceBreakpointHitCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "sourceBreakpointLogMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))))

data SourcePresentationHint Source #

Instances

Instances details
FromJSON SourcePresentationHint Source # 
Instance details

Defined in DAP.Types

ToJSON SourcePresentationHint Source # 
Instance details

Defined in DAP.Types

Generic SourcePresentationHint Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep SourcePresentationHint :: Type -> Type Source #

Show SourcePresentationHint Source # 
Instance details

Defined in DAP.Types

Eq SourcePresentationHint Source # 
Instance details

Defined in DAP.Types

type Rep SourcePresentationHint Source # 
Instance details

Defined in DAP.Types

type Rep SourcePresentationHint = D1 ('MetaData "SourcePresentationHint" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SourcePresentationHintNormal" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourcePresentationHintEmphasize" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourcePresentationHintDeemphasize" 'PrefixI 'False) (U1 :: Type -> Type)))

data StackFrame Source #

Constructors

StackFrame 

Fields

  • stackFrameId :: 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 scopes request or to restart the execution of a stack frame.

  • stackFrameName :: Text

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

  • stackFrameSource :: Maybe Source

    The source of the frame.

  • stackFrameLine :: Int

    The line within the source of the frame. If the source attribute is missing or doesn't exist, line is 0 and should be ignored by the client.

  • stackFrameColumn :: Int

    Start position of the range covered by the stack frame. It is measured in UTF-16 code units and the client capability columnsStartAt1 determines whether it is 0- or 1-based. If attribute source is missing or doesn't exist, column is 0 and should be ignored by the client.

  • stackFrameEndLine :: Maybe Int

    The end line of the range covered by the stack frame.

  • stackFrameEndColumn :: Maybe Int

    End position of the range covered by the stack frame. It is measured in UTF-16 code units and the client capability columnsStartAt1 determines whether it is 0- or 1-based.

  • stackFrameCanRestart :: Maybe Bool

    Indicates whether this frame can be restarted with the restart request. Clients should only use this if the debug adapter supports the restart request and the corresponding capability supportsRestartRequest is true. If a debug adapter has this capability, then canRestart defaults to true if the property is absent.

  • stackFrameInstructionPointerReference :: Maybe Text

    A memory reference for the current instruction pointer in this frame.

  • stackFrameModuleId :: Maybe (Either Int Text)

    The module associated with this frame, if any.

  • stackFramePresentationHint :: Maybe PresentationHint

    A hint for how to present this frame in the UI. A value of label can be used to indicate that the frame is an artificial frame that is used as a visual label or separator. A value of subtle can be used to change the appearance of a frame in a subtle way. Values: normal, label, subtle

Instances

Instances details
ToJSON StackFrame Source # 
Instance details

Defined in DAP.Types

Generic StackFrame Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep StackFrame :: Type -> Type Source #

Show StackFrame Source # 
Instance details

Defined in DAP.Types

Eq StackFrame Source # 
Instance details

Defined in DAP.Types

type Rep StackFrame Source # 
Instance details

Defined in DAP.Types

data StackFrameFormat Source #

Constructors

StackFrameFormat 

Fields

Instances

Instances details
FromJSON StackFrameFormat Source # 
Instance details

Defined in DAP.Types

Generic StackFrameFormat Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep StackFrameFormat :: Type -> Type Source #

Show StackFrameFormat Source # 
Instance details

Defined in DAP.Types

Eq StackFrameFormat Source # 
Instance details

Defined in DAP.Types

type Rep StackFrameFormat Source # 
Instance details

Defined in DAP.Types

type Rep StackFrameFormat = D1 ('MetaData "StackFrameFormat" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "StackFrameFormat" 'PrefixI 'True) (((S1 ('MetaSel ('Just "stackFrameFormatParameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "stackFrameFormatParameterTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "stackFrameFormatParameterNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "stackFrameFormatParameterValues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "stackFrameFormatLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "stackFrameFormatModule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "stackFrameFormatIncludeAll") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "stackFrameFormatHex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))))

data StepInTarget Source #

Constructors

StepInTarget 

Fields

Instances

Instances details
ToJSON StepInTarget Source # 
Instance details

Defined in DAP.Types

Generic StepInTarget Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep StepInTarget :: Type -> Type Source #

Show StepInTarget Source # 
Instance details

Defined in DAP.Types

Eq StepInTarget Source # 
Instance details

Defined in DAP.Types

type Rep StepInTarget Source # 
Instance details

Defined in DAP.Types

type Rep StepInTarget = D1 ('MetaData "StepInTarget" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "StepInTarget" 'PrefixI 'True) ((S1 ('MetaSel ('Just "stepInTargetId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "stepInTargetLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "stepInTargetLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))) :*: (S1 ('MetaSel ('Just "stepInTargetColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "stepInTargetEndLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "stepInTargetEndColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))))

data SteppingGranularity Source #

Instances

Instances details
FromJSON SteppingGranularity Source # 
Instance details

Defined in DAP.Types

Generic SteppingGranularity Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep SteppingGranularity :: Type -> Type Source #

Show SteppingGranularity Source # 
Instance details

Defined in DAP.Types

Eq SteppingGranularity Source # 
Instance details

Defined in DAP.Types

type Rep SteppingGranularity Source # 
Instance details

Defined in DAP.Types

type Rep SteppingGranularity = D1 ('MetaData "SteppingGranularity" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SteppingGranularityStatement" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SteppingGranularityLine" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SteppingGranularityInstruction" 'PrefixI 'False) (U1 :: Type -> Type)))

data Thread Source #

Constructors

Thread 

Fields

Instances

Instances details
FromJSON Thread Source # 
Instance details

Defined in DAP.Types

ToJSON Thread Source # 
Instance details

Defined in DAP.Types

Generic Thread Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep Thread :: Type -> Type Source #

Show Thread Source # 
Instance details

Defined in DAP.Types

Eq Thread Source # 
Instance details

Defined in DAP.Types

type Rep Thread Source # 
Instance details

Defined in DAP.Types

type Rep Thread = D1 ('MetaData "Thread" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "Thread" 'PrefixI 'True) (S1 ('MetaSel ('Just "threadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "threadName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data ThreadEventReason Source #

Instances

Instances details
ToJSON ThreadEventReason Source # 
Instance details

Defined in DAP.Types

Generic ThreadEventReason Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ThreadEventReason :: Type -> Type Source #

Show ThreadEventReason Source # 
Instance details

Defined in DAP.Types

Eq ThreadEventReason Source # 
Instance details

Defined in DAP.Types

type Rep ThreadEventReason Source # 
Instance details

Defined in DAP.Types

type Rep ThreadEventReason = D1 ('MetaData "ThreadEventReason" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ThreadEventReasonStarted" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ThreadEventReasonExited" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ThreadEventReason" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data ValueFormat Source #

Constructors

ValueFormat 

Fields

Instances

Instances details
FromJSON ValueFormat Source # 
Instance details

Defined in DAP.Types

Generic ValueFormat Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ValueFormat :: Type -> Type Source #

Show ValueFormat Source # 
Instance details

Defined in DAP.Types

Eq ValueFormat Source # 
Instance details

Defined in DAP.Types

type Rep ValueFormat Source # 
Instance details

Defined in DAP.Types

type Rep ValueFormat = D1 ('MetaData "ValueFormat" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ValueFormat" 'PrefixI 'True) (S1 ('MetaSel ('Just "valueFormatHex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))

data Variable Source #

Constructors

Variable 

Fields

  • variableName :: Text

    The variable's name.

  • variableValue :: Text

    The variable's value. This can be a multi-line text, e.g. for a function the body of a function. For structured variables (which do not have a simple value), it is recommended to provide a one-line representation of the structured object. This helps to identify the structured object in the collapsed state when its children are not yet visible. An empty string can be used if no value should be shown in the UI.

  • variableType :: Maybe Text

    The type of the variable's value. Typically shown in the UI when hovering over the value. This attribute should only be returned by a debug adapter if the corresponding capability supportsVariableType is true.

  • variablePresentationHint :: Maybe VariablePresentationHint

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

  • variableEvaluateName :: Maybe Text

    The evaluatable name of this variable which can be passed to the evaluate request to fetch the variable's value.

  • variableVariablesReference :: Int

    If variablesReference is > 0, the variable is structured and its children can be retrieved by passing variablesReference to the variables request as long as execution remains suspended. See 'Lifetime of Object References' in the Overview section for details.

  • variableNamedVariables :: Maybe Int

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

  • variableIndexedVariables :: Maybe Int

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

  • variableMemoryReference :: Maybe Text

    The memory reference for the variable if the variable represents executable code, such as a function pointer. This attribute is only required if the corresponding capability supportsMemoryReferences is true.

Instances

Instances details
ToJSON Variable Source # 
Instance details

Defined in DAP.Types

Generic Variable Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep Variable :: Type -> Type Source #

Show Variable Source # 
Instance details

Defined in DAP.Types

Eq Variable Source # 
Instance details

Defined in DAP.Types

type Rep Variable Source # 
Instance details

Defined in DAP.Types

data VariablePresentationHint Source #

Constructors

VariablePresentationHint 

Fields

  • variablePresentationHintKind :: Maybe PresentationHintKind

    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. dataBreakpoint: Deprecated: Indicates that a data breakpoint is registered for the object. The hasDataBreakpoint attribute should generally be used instead. etc.

  • variablePresentationHintAttributes :: Maybe [PresentationHintAttributes]

    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. rawText: 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. hasDataBreakpoint: Indicates that the object has its value tracked by a data breakpoint. etc.

  • variablePresentationHintVisibility :: Maybe PresentationHintVisibility

    Visibility of variable. Before introducing additional values, try to use the listed values. Values: public, private, protected, internal, final, etc.

  • variablePresentationHintLazy :: Maybe Bool

    If true, clients can present the variable with a UI that supports a specific gesture to trigger its evaluation. This mechanism can be used for properties that require executing code when retrieving their value and where the code execution can be expensive and/or produce side-effects. A typical example are properties based on a getter function. Please note that in addition to the lazy flag, the variable's variablesReference is expected to refer to a variable that will provide the value through another variable request.

Instances

Instances details
ToJSON VariablePresentationHint Source # 
Instance details

Defined in DAP.Types

Generic VariablePresentationHint Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep VariablePresentationHint :: Type -> Type Source #

Show VariablePresentationHint Source # 
Instance details

Defined in DAP.Types

Eq VariablePresentationHint Source # 
Instance details

Defined in DAP.Types

type Rep VariablePresentationHint Source # 
Instance details

Defined in DAP.Types

type Rep VariablePresentationHint = D1 ('MetaData "VariablePresentationHint" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "VariablePresentationHint" 'PrefixI 'True) ((S1 ('MetaSel ('Just "variablePresentationHintKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PresentationHintKind)) :*: S1 ('MetaSel ('Just "variablePresentationHintAttributes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PresentationHintAttributes]))) :*: (S1 ('MetaSel ('Just "variablePresentationHintVisibility") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PresentationHintVisibility)) :*: S1 ('MetaSel ('Just "variablePresentationHintLazy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))

data ColumnDescriptorType Source #

Instances

Instances details
ToJSON ColumnDescriptorType Source # 
Instance details

Defined in DAP.Types

Generic ColumnDescriptorType Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ColumnDescriptorType :: Type -> Type Source #

Show ColumnDescriptorType Source # 
Instance details

Defined in DAP.Types

Eq ColumnDescriptorType Source # 
Instance details

Defined in DAP.Types

type Rep ColumnDescriptorType Source # 
Instance details

Defined in DAP.Types

type Rep ColumnDescriptorType = D1 ('MetaData "ColumnDescriptorType" "DAP.Types" "dap-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "ColumnDescriptorTypeString" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ColumnDescriptorTypeInt" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ColumnDescriptorTypeBool" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ColumnDescriptorTypeUTCTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime))))

data ScopePresentationHint Source #

Instances

Instances details
ToJSON ScopePresentationHint Source # 
Instance details

Defined in DAP.Types

Generic ScopePresentationHint Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ScopePresentationHint :: Type -> Type Source #

Show ScopePresentationHint Source # 
Instance details

Defined in DAP.Types

Eq ScopePresentationHint Source # 
Instance details

Defined in DAP.Types

type Rep ScopePresentationHint Source # 
Instance details

Defined in DAP.Types

type Rep ScopePresentationHint = D1 ('MetaData "ScopePresentationHint" "DAP.Types" "dap-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "ScopePresentationHintArguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScopePresentationHintLocals" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ScopePresentationHintRegisters" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScopePresentationHint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data PresentationHintKind Source #

Instances

Instances details
ToJSON PresentationHintKind Source # 
Instance details

Defined in DAP.Types

Generic PresentationHintKind Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep PresentationHintKind :: Type -> Type Source #

Show PresentationHintKind Source # 
Instance details

Defined in DAP.Types

Eq PresentationHintKind Source # 
Instance details

Defined in DAP.Types

type Rep PresentationHintKind Source # 
Instance details

Defined in DAP.Types

type Rep PresentationHintKind = D1 ('MetaData "PresentationHintKind" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (((C1 ('MetaCons "PresentationHintKindProperty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PresentationHintKindMethod" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PresentationHintKindClass" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PresentationHintKindData" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PresentationHintKindEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PresentationHintKindBaseClass" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PresentationHintKindInnerClass" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PresentationHintKindInterface" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PresentationHintKindMostDerivedClass" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PresentationHintKindVirtual" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PresentationHintKindDataBreakpoint" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PresentationHintKind" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))))

data PresentationHintAttributes Source #

Instances

Instances details
ToJSON PresentationHintAttributes Source #

attributes?: (static | constant | readOnly | rawText | hasObjectId canHaveObjectId | hasSideEffects | hasDataBreakpoint | string)[];

Instance details

Defined in DAP.Types

Generic PresentationHintAttributes Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep PresentationHintAttributes :: Type -> Type Source #

Show PresentationHintAttributes Source # 
Instance details

Defined in DAP.Types

Eq PresentationHintAttributes Source # 
Instance details

Defined in DAP.Types

type Rep PresentationHintAttributes Source # 
Instance details

Defined in DAP.Types

type Rep PresentationHintAttributes = D1 ('MetaData "PresentationHintAttributes" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (((C1 ('MetaCons "PresentationHintAttributesStatic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PresentationHintAttributesConstant" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PresentationHintAttributesReadOnly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PresentationHintAttributesRawText" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PresentationHintAttributesHasObjectId" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PresentationHintAttributesCanHaveObjectId" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PresentationHintAttributesHasSideEffects" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PresentationHintAttributesHasDataBreakpoint" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PresentationHintAttributes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))

data PresentationHintVisibility Source #

Instances

Instances details
ToJSON PresentationHintVisibility Source #

?: public | private | protected | internal | final | string;

Instance details

Defined in DAP.Types

Generic PresentationHintVisibility Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep PresentationHintVisibility :: Type -> Type Source #

Show PresentationHintVisibility Source # 
Instance details

Defined in DAP.Types

Eq PresentationHintVisibility Source # 
Instance details

Defined in DAP.Types

type Rep PresentationHintVisibility Source # 
Instance details

Defined in DAP.Types

type Rep PresentationHintVisibility = D1 ('MetaData "PresentationHintVisibility" "DAP.Types" "dap-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "PresentationHintVisibilityPublic" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PresentationHintVisibilityPrivate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PresentationHintVisibilityProtected" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PresentationHintVisibilityInternal" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PresentationHintVisibilityFinal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PresentationHintVisibility" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

data EventGroup Source #

Instances

Instances details
ToJSON EventGroup Source # 
Instance details

Defined in DAP.Types

Generic EventGroup Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep EventGroup :: Type -> Type Source #

Show EventGroup Source # 
Instance details

Defined in DAP.Types

Eq EventGroup Source # 
Instance details

Defined in DAP.Types

type Rep EventGroup Source # 
Instance details

Defined in DAP.Types

type Rep EventGroup = D1 ('MetaData "EventGroup" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "EventGroupStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EventGroupStartCollapsed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventGroupEnd" 'PrefixI 'False) (U1 :: Type -> Type)))

data EventReason Source #

Instances

Instances details
ToJSON EventReason Source # 
Instance details

Defined in DAP.Types

Generic EventReason Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep EventReason :: Type -> Type Source #

Show EventReason Source # 
Instance details

Defined in DAP.Types

Eq EventReason Source # 
Instance details

Defined in DAP.Types

type Rep EventReason Source # 
Instance details

Defined in DAP.Types

type Rep EventReason = D1 ('MetaData "EventReason" "DAP.Types" "dap-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "EventReasonNew" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventReasonChanged" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EventReasonRemoved" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventReason" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data StartMethod Source #

Instances

Instances details
ToJSON StartMethod Source # 
Instance details

Defined in DAP.Types

Generic StartMethod Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep StartMethod :: Type -> Type Source #

Show StartMethod Source # 
Instance details

Defined in DAP.Types

Eq StartMethod Source # 
Instance details

Defined in DAP.Types

type Rep StartMethod Source # 
Instance details

Defined in DAP.Types

type Rep StartMethod = D1 ('MetaData "StartMethod" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "StartMethodLaunch" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StartMethodAttach" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StartMethodAttachForSuspendedLaunch" 'PrefixI 'False) (U1 :: Type -> Type)))

data EvaluateArgumentsContext Source #

Instances

Instances details
FromJSON EvaluateArgumentsContext Source # 
Instance details

Defined in DAP.Types

ToJSON EvaluateArgumentsContext Source # 
Instance details

Defined in DAP.Types

Generic EvaluateArgumentsContext Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep EvaluateArgumentsContext :: Type -> Type Source #

Show EvaluateArgumentsContext Source # 
Instance details

Defined in DAP.Types

Eq EvaluateArgumentsContext Source # 
Instance details

Defined in DAP.Types

type Rep EvaluateArgumentsContext Source # 
Instance details

Defined in DAP.Types

type Rep EvaluateArgumentsContext = D1 ('MetaData "EvaluateArgumentsContext" "DAP.Types" "dap-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "EvaluateArgumentsContextWatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EvaluateArgumentsContextRepl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EvaluateArgumentsContextHover" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EvaluateArgumentsContextClipboard" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EvaluateArgumentsContextVariable" 'PrefixI 'False) (U1 :: Type -> Type))))

data PathFormat Source #

Constructors

Path 
URI 
PathFormat Text 

Instances

Instances details
FromJSON PathFormat Source # 
Instance details

Defined in DAP.Types

Show PathFormat Source # 
Instance details

Defined in DAP.Types

Eq PathFormat Source # 
Instance details

Defined in DAP.Types

Command

data Command Source #

Instances

Instances details
FromJSON Command Source # 
Instance details

Defined in DAP.Types

ToJSON Command Source # 
Instance details

Defined in DAP.Types

Generic Command Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep Command :: Type -> Type Source #

Read Command Source # 
Instance details

Defined in DAP.Types

Show Command Source # 
Instance details

Defined in DAP.Types

Eq Command Source # 
Instance details

Defined in DAP.Types

type Rep Command Source # 
Instance details

Defined in DAP.Types

type Rep Command = D1 ('MetaData "Command" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (((((C1 ('MetaCons "CommandCancel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandRunInTerminal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CommandStartDebugging" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandInitialize" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandConfigurationDone" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CommandLaunch" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandAttach" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandRestart" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CommandDisconnect" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandTerminate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandBreakpointLocations" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CommandSetBreakpoints" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandSetFunctionBreakpoints" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CommandSetExceptionBreakpoints" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandDataBreakpointInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandSetDataBreakpoints" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CommandSetInstructionBreakpoints" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandContinue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandNext" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CommandStepIn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandStepOut" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandStepBack" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "CommandReverseContinue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandRestartFrame" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CommandGoTo" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandPause" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandStackTrace" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CommandScopes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandVariables" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandSetVariable" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CommandSource" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandThreads" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandTerminateThreads" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CommandModules" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandLoadedSources" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandEvaluate" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CommandSetExpression" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandStepInTargets" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandGoToTargets" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CommandCompletions" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandExceptionInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommandReadMemory" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CommandWriteMemory" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CommandDisassemble" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CustomCommand" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))))))

Event

data EventType Source #

Instances

Instances details
ToJSON EventType Source # 
Instance details

Defined in DAP.Types

Generic EventType Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep EventType :: Type -> Type Source #

Read EventType Source # 
Instance details

Defined in DAP.Types

Show EventType Source # 
Instance details

Defined in DAP.Types

Eq EventType Source # 
Instance details

Defined in DAP.Types

type Rep EventType Source # 
Instance details

Defined in DAP.Types

type Rep EventType = D1 ('MetaData "EventType" "DAP.Types" "dap-0.1.0.0-inplace" 'False) ((((C1 ('MetaCons "EventTypeInitialized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventTypeStopped" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EventTypeContinued" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventTypeExited" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EventTypeTerminated" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventTypeThread" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EventTypeOutput" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventTypeBreakpoint" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "EventTypeModule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventTypeLoadedSource" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EventTypeProcess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventTypeCapabilities" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EventTypeProgressStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventTypeProgressUpdate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EventTypeProgressEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EventTypeInvalidated" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventTypeMemory" 'PrefixI 'False) (U1 :: Type -> Type))))))

Events

data StoppedEvent Source #

Constructors

StoppedEvent 

Fields

  • stoppedEventReason :: StoppedEventReason

    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, goto, 'function breakpoint', 'data breakpoint', 'instruction breakpoint', etc.

  • stoppedEventDescription :: Maybe Text

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

  • stoppedEventThreadId :: Maybe Int

    The thread which was stopped.

  • stoppedEventPreserveFocusHint :: Bool

    A value of true hints to the client that this event should not change the focus.

  • stoppedEventText :: Maybe Text

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

  • stoppedEventAllThreadsStopped :: 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.

  • stoppedEventHitBreakpointIds :: [Int]

    Ids of the breakpoints that triggered the event. In most cases there is only a single breakpoint but here are some examples for multiple breakpoints: - Different types of breakpoints map to the same location. - Multiple source breakpoints get collapsed to the same instruction by the compiler/runtime. - Multiple function breakpoints with different function names map to the same location.

Instances

Instances details
ToJSON StoppedEvent Source # 
Instance details

Defined in DAP.Types

Generic StoppedEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep StoppedEvent :: Type -> Type Source #

Show StoppedEvent Source # 
Instance details

Defined in DAP.Types

Eq StoppedEvent Source # 
Instance details

Defined in DAP.Types

type Rep StoppedEvent Source # 
Instance details

Defined in DAP.Types

type Rep StoppedEvent = D1 ('MetaData "StoppedEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "StoppedEvent" 'PrefixI 'True) ((S1 ('MetaSel ('Just "stoppedEventReason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StoppedEventReason) :*: (S1 ('MetaSel ('Just "stoppedEventDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "stoppedEventThreadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))) :*: ((S1 ('MetaSel ('Just "stoppedEventPreserveFocusHint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "stoppedEventText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "stoppedEventAllThreadsStopped") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "stoppedEventHitBreakpointIds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])))))

data ContinuedEvent Source #

Constructors

ContinuedEvent 

Fields

Instances

Instances details
ToJSON ContinuedEvent Source # 
Instance details

Defined in DAP.Types

Generic ContinuedEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ContinuedEvent :: Type -> Type Source #

Show ContinuedEvent Source # 
Instance details

Defined in DAP.Types

Eq ContinuedEvent Source # 
Instance details

Defined in DAP.Types

type Rep ContinuedEvent Source # 
Instance details

Defined in DAP.Types

type Rep ContinuedEvent = D1 ('MetaData "ContinuedEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ContinuedEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "continuedEventThreadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "continuedEventAllThreadsContinued") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data ExitedEvent Source #

Constructors

ExitedEvent 

Fields

Instances

Instances details
ToJSON ExitedEvent Source # 
Instance details

Defined in DAP.Types

Generic ExitedEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ExitedEvent :: Type -> Type Source #

Show ExitedEvent Source # 
Instance details

Defined in DAP.Types

Eq ExitedEvent Source # 
Instance details

Defined in DAP.Types

type Rep ExitedEvent Source # 
Instance details

Defined in DAP.Types

type Rep ExitedEvent = D1 ('MetaData "ExitedEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ExitedEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "exitedEventExitCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data TerminatedEvent Source #

Constructors

TerminatedEvent 

Fields

  • terminatedEventRestart :: Bool

    A debug adapter may set restart to true (or to an arbitrary object) to request that the client restarts the session. The value is not interpreted by the client and passed unmodified as an attribute __restart to the launch and attach requests.

Instances

Instances details
ToJSON TerminatedEvent Source # 
Instance details

Defined in DAP.Types

Generic TerminatedEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep TerminatedEvent :: Type -> Type Source #

Show TerminatedEvent Source # 
Instance details

Defined in DAP.Types

Eq TerminatedEvent Source # 
Instance details

Defined in DAP.Types

type Rep TerminatedEvent Source # 
Instance details

Defined in DAP.Types

type Rep TerminatedEvent = D1 ('MetaData "TerminatedEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "TerminatedEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "terminatedEventRestart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data ThreadEvent Source #

Constructors

ThreadEvent 

Fields

Instances

Instances details
ToJSON ThreadEvent Source # 
Instance details

Defined in DAP.Types

Generic ThreadEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ThreadEvent :: Type -> Type Source #

Show ThreadEvent Source # 
Instance details

Defined in DAP.Types

Eq ThreadEvent Source # 
Instance details

Defined in DAP.Types

type Rep ThreadEvent Source # 
Instance details

Defined in DAP.Types

type Rep ThreadEvent = D1 ('MetaData "ThreadEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ThreadEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "threadEventReason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ThreadEventReason) :*: S1 ('MetaSel ('Just "threadEventThreadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data OutputEvent Source #

Constructors

OutputEvent 

Fields

  • outputEventCategory :: Maybe OutputEventCategory

    The output category. If not specified or if the category is not understood by the client, console is assumed. Values: console: Show the output in the client's default message UI, e.g. a 'debug console'. This category should only be used for informational output from the debugger (as opposed to the debuggee). important: A hint for the client to show the output in the client's UI for important and highly visible information, e.g. as a popup notification. This category should only be used for important messages from the debugger (as opposed to the debuggee). Since this category value is a hint, clients might ignore the hint and assume the console category. stdout: Show the output as normal program output from the debuggee. stderr: Show the output as error program output from the debuggee. telemetry: Send the output to telemetry instead of showing it to the user. etc.

  • outputEventOutput :: Text

    The output to report.

  • outputEventGroup :: Maybe EventGroup

    Support for keeping an output log organized by grouping related messages. Values: start: Start a new group in expanded mode. Subsequent output events are members of the group and should be shown indented. The output attribute becomes the name of the group and is not indented. startCollapsed: Start a new group in collapsed mode. Subsequent output events are members of the group and should be shown indented (as soon as the group is expanded). The output attribute becomes the name of the group and is not indented. end: End the current group and decrease the indentation of subsequent output events. A non-empty output attribute is shown as the unindented end of the group.

  • outputEventVariablesReference :: Maybe Int

    If an attribute variablesReference exists and its value is > 0, the output contains objects which can be retrieved by passing variablesReference to the variables request as long as execution remains suspended. See 'Lifetime of Object References' in the Overview section for details.

  • outputEventSource :: Maybe Source

    The source location where the output was produced.

  • outputEventLine :: Maybe Int

    The source location's line where the output was produced.

  • outputEventColumn :: Maybe Int

    The position in line where the output was produced. It is measured in UTF-16 code units and the client capability columnsStartAt1 determines whether it is 0- or 1-based.

  • outputEventData :: Maybe Value

    Additional data to report. For the telemetry category the data is sent to telemetry, for the other categories the data is shown in JSON format.

Instances

Instances details
ToJSON OutputEvent Source # 
Instance details

Defined in DAP.Types

Generic OutputEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep OutputEvent :: Type -> Type Source #

Show OutputEvent Source # 
Instance details

Defined in DAP.Types

Eq OutputEvent Source # 
Instance details

Defined in DAP.Types

type Rep OutputEvent Source # 
Instance details

Defined in DAP.Types

data BreakpointEvent Source #

Constructors

BreakpointEvent 

Fields

Instances

Instances details
ToJSON BreakpointEvent Source # 
Instance details

Defined in DAP.Types

Generic BreakpointEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep BreakpointEvent :: Type -> Type Source #

Show BreakpointEvent Source # 
Instance details

Defined in DAP.Types

Eq BreakpointEvent Source # 
Instance details

Defined in DAP.Types

type Rep BreakpointEvent Source # 
Instance details

Defined in DAP.Types

type Rep BreakpointEvent = D1 ('MetaData "BreakpointEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "BreakpointEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "breakpointEventReason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EventReason) :*: S1 ('MetaSel ('Just "breakpointEvevntBreakpoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Breakpoint)))

data ModuleEvent Source #

Constructors

ModuleEvent 

Fields

data ProcessEvent Source #

Constructors

ProcessEvent 

Fields

  • processEventName :: Text

    The logical name of the process. This is usually the full path to process's executable file. Example: homeexamplemyprojprogram.js.

  • processEventSystemProcessId :: Maybe Int

    The system process id of the debugged process. This property is missing for non-system processes.

  • processEventIsLocalProcess :: Bool

    If true, the process is running on the same computer as the debug adapter.

  • processEventStartMethod :: Maybe StartMethod

    Describes how the debug engine started debugging this process. Values: launch: Process was launched under the debugger. attach: Debugger attached to an existing process. attachForSuspendedLaunch: A project launcher component has launched a new process in a suspended state and then asked the debugger to attach.

  • processEventPointerSize :: Maybe Int

    The size of a pointer or address for this process, in bits. This value may be used by clients when formatting addresses for display.

Instances

Instances details
ToJSON ProcessEvent Source # 
Instance details

Defined in DAP.Types

Generic ProcessEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ProcessEvent :: Type -> Type Source #

Show ProcessEvent Source # 
Instance details

Defined in DAP.Types

Eq ProcessEvent Source # 
Instance details

Defined in DAP.Types

type Rep ProcessEvent Source # 
Instance details

Defined in DAP.Types

type Rep ProcessEvent = D1 ('MetaData "ProcessEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ProcessEvent" 'PrefixI 'True) ((S1 ('MetaSel ('Just "processEventName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "processEventSystemProcessId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "processEventIsLocalProcess") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "processEventStartMethod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StartMethod)) :*: S1 ('MetaSel ('Just "processEventPointerSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))))

data CapabilitiesEvent Source #

Constructors

CapabilitiesEvent 

Fields

data ProgressStartEvent Source #

Constructors

ProgressStartEvent 

Fields

  • progressStartEventProgressId :: Text

    An ID that can be used in subsequent progressUpdate and progressEnd events to make them refer to the same progress reporting. IDs must be unique within a debug session.

  • progressStartEventTitle :: Text

    Short title of the progress reporting. Shown in the UI to describe the long running operation.

  • progressStartEventRequestId :: Maybe Int

    The request ID that this progress report is related to. If specified a debug adapter is expected to emit progress events for the long running request until the request has been either completed or cancelled. If the request ID is omitted, the progress report is assumed to be related to some general activity of the debug adapter.

  • progressStartEventCancellable :: Bool

    If true, the request that reports progress may be cancelled with a cancel request. So this property basically controls whether the client should use UX that supports cancellation. Clients that don't support cancellation are allowed to ignore the setting.

  • progressStartEventMessage :: Maybe Text

    More detailed progress message.

  • progressStartEventPercentage :: Maybe Int

    Progress percentage to display (value range: 0 to 100). If omitted no percentage is shown.

Instances

Instances details
ToJSON ProgressStartEvent Source # 
Instance details

Defined in DAP.Types

Generic ProgressStartEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ProgressStartEvent :: Type -> Type Source #

Show ProgressStartEvent Source # 
Instance details

Defined in DAP.Types

Eq ProgressStartEvent Source # 
Instance details

Defined in DAP.Types

type Rep ProgressStartEvent Source # 
Instance details

Defined in DAP.Types

type Rep ProgressStartEvent = D1 ('MetaData "ProgressStartEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ProgressStartEvent" 'PrefixI 'True) ((S1 ('MetaSel ('Just "progressStartEventProgressId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "progressStartEventTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "progressStartEventRequestId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))) :*: (S1 ('MetaSel ('Just "progressStartEventCancellable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "progressStartEventMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "progressStartEventPercentage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))))

data ProgressUpdateEvent Source #

Constructors

ProgressUpdateEvent 

Fields

Instances

Instances details
ToJSON ProgressUpdateEvent Source # 
Instance details

Defined in DAP.Types

Generic ProgressUpdateEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ProgressUpdateEvent :: Type -> Type Source #

Show ProgressUpdateEvent Source # 
Instance details

Defined in DAP.Types

Eq ProgressUpdateEvent Source # 
Instance details

Defined in DAP.Types

type Rep ProgressUpdateEvent Source # 
Instance details

Defined in DAP.Types

type Rep ProgressUpdateEvent = D1 ('MetaData "ProgressUpdateEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ProgressUpdateEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "progressUpdateEventProgressId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "progressUpdateEventMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "progressUpdateEventPercentage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))

data ProgressEndEvent Source #

Constructors

ProgressEndEvent 

Fields

Instances

Instances details
ToJSON ProgressEndEvent Source # 
Instance details

Defined in DAP.Types

Generic ProgressEndEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ProgressEndEvent :: Type -> Type Source #

Show ProgressEndEvent Source # 
Instance details

Defined in DAP.Types

Eq ProgressEndEvent Source # 
Instance details

Defined in DAP.Types

type Rep ProgressEndEvent Source # 
Instance details

Defined in DAP.Types

type Rep ProgressEndEvent = D1 ('MetaData "ProgressEndEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ProgressEndEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "progressEndEventProgressId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "progressEndEventMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))

data InvalidatedEvent Source #

Constructors

InvalidatedEvent 

Fields

  • invalidatedEventAreas :: [InvalidatedAreas]

    Set of logical areas that got invalidated. This property has a hint characteristic: a client can only be expected to make a 'best effort' in honoring the areas but there are no guarantees. If this property is missing, empty, or if values are not understood, the client should assume a single value all.

  • invalidatedEventThreadId :: Maybe Int

    If specified, the client only needs to refetch data related to this thread.

  • invalidatedEventStackFrameId :: Maybe Int

    If specified, the client only needs to refetch data related to this stack frame (and the threadId is ignored).

Instances

Instances details
ToJSON InvalidatedEvent Source # 
Instance details

Defined in DAP.Types

Generic InvalidatedEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep InvalidatedEvent :: Type -> Type Source #

Show InvalidatedEvent Source # 
Instance details

Defined in DAP.Types

Eq InvalidatedEvent Source # 
Instance details

Defined in DAP.Types

type Rep InvalidatedEvent Source # 
Instance details

Defined in DAP.Types

type Rep InvalidatedEvent = D1 ('MetaData "InvalidatedEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "InvalidatedEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "invalidatedEventAreas") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InvalidatedAreas]) :*: (S1 ('MetaSel ('Just "invalidatedEventThreadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "invalidatedEventStackFrameId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))

data MemoryEvent Source #

Constructors

MemoryEvent 

Fields

Instances

Instances details
ToJSON MemoryEvent Source # 
Instance details

Defined in DAP.Types

Generic MemoryEvent Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep MemoryEvent :: Type -> Type Source #

Show MemoryEvent Source # 
Instance details

Defined in DAP.Types

Eq MemoryEvent Source # 
Instance details

Defined in DAP.Types

type Rep MemoryEvent Source # 
Instance details

Defined in DAP.Types

type Rep MemoryEvent = D1 ('MetaData "MemoryEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "MemoryEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "memoryEventMemoryReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "memoryEventOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "memoryEventCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

Server

data ServerConfig Source #

Instances

Instances details
Show ServerConfig Source # 
Instance details

Defined in DAP.Types

Eq ServerConfig Source # 
Instance details

Defined in DAP.Types

Client

newtype Adaptor store a Source #

Core type for Debug Adaptor to send and receive messages in a type safe way. the state is AdaptorState which holds configuration information, along with the current event / response being constructed and the type of the message. Of note: A StateT is used because adaptorPayload should not be shared with other threads.

Instances

Instances details
MonadBaseControl IO (Adaptor store) Source # 
Instance details

Defined in DAP.Types

Associated Types

type StM (Adaptor store) a Source #

Methods

liftBaseWith :: (RunInBase (Adaptor store) IO -> IO a) -> Adaptor store a Source #

restoreM :: StM (Adaptor store) a -> Adaptor store a Source #

MonadBase IO (Adaptor store) Source # 
Instance details

Defined in DAP.Types

Methods

liftBase :: IO α -> Adaptor store α Source #

MonadIO (Adaptor store) Source # 
Instance details

Defined in DAP.Types

Methods

liftIO :: IO a -> Adaptor store a Source #

Applicative (Adaptor store) Source # 
Instance details

Defined in DAP.Types

Methods

pure :: a -> Adaptor store a Source #

(<*>) :: Adaptor store (a -> b) -> Adaptor store a -> Adaptor store b Source #

liftA2 :: (a -> b -> c) -> Adaptor store a -> Adaptor store b -> Adaptor store c Source #

(*>) :: Adaptor store a -> Adaptor store b -> Adaptor store b Source #

(<*) :: Adaptor store a -> Adaptor store b -> Adaptor store a Source #

Functor (Adaptor store) Source # 
Instance details

Defined in DAP.Types

Methods

fmap :: (a -> b) -> Adaptor store a -> Adaptor store b Source #

(<$) :: a -> Adaptor store b -> Adaptor store a Source #

Monad (Adaptor store) Source # 
Instance details

Defined in DAP.Types

Methods

(>>=) :: Adaptor store a -> (a -> Adaptor store b) -> Adaptor store b Source #

(>>) :: Adaptor store a -> Adaptor store b -> Adaptor store b Source #

return :: a -> Adaptor store a Source #

MonadState (AdaptorState store) (Adaptor store) Source # 
Instance details

Defined in DAP.Types

Methods

get :: Adaptor store (AdaptorState store) Source #

put :: AdaptorState store -> Adaptor store () Source #

state :: (AdaptorState store -> (a, AdaptorState store)) -> Adaptor store a Source #

MonadError (ErrorMessage, Maybe Message) (Adaptor store) Source # 
Instance details

Defined in DAP.Types

Methods

throwError :: (ErrorMessage, Maybe Message) -> Adaptor store a Source #

catchError :: Adaptor store a -> ((ErrorMessage, Maybe Message) -> Adaptor store a) -> Adaptor store a Source #

type StM (Adaptor store) a Source # 
Instance details

Defined in DAP.Types

type StM (Adaptor store) a = StM (ExceptT (ErrorMessage, Maybe Message) (StateT (AdaptorState store) IO)) a

data AdaptorState app Source #

The adaptor state is local to a single connection / thread

Constructors

AdaptorState 

Fields

  • messageType :: MessageType

    Current message type being created This was added as a convenience so we can set the request_seq and command fields automatically.

  • payload :: ![Pair]

    Payload of the current message to be sent This should never be manually modified by the end user The payload is accumulated automatically by usage of the API

  • appStore :: AppStore app

    Global app store, accessible on a per session basis Initialized during attach sessions

  • serverConfig :: ServerConfig

    Configuration information for the ServerConfig Identical across all debugging sessions

  • handle :: Handle

    Connection Handle

  • request :: Request

    Connection Request information

  • address :: SockAddr

    Address of Connection

  • sessionId :: Maybe SessionId

    Session ID Local to the current connection's debugger session

  • adaptorStateMVar :: MVar (AdaptorState app)

    Shared state for serializable concurrency

  • handleLock :: MVar ()

    A lock for writing to a Handle. One lock is created per connection and exists for the duration of that connection

Instances

Instances details
MonadState (AdaptorState store) (Adaptor store) Source # 
Instance details

Defined in DAP.Types

Methods

get :: Adaptor store (AdaptorState store) Source #

put :: AdaptorState store -> Adaptor store () Source #

state :: (AdaptorState store -> (a, AdaptorState store)) -> Adaptor store a Source #

type AppStore app = TVar (HashMap SessionId (DebuggerThreadState, app)) Source #

Used to store a map of debugging sessions The ThreadId is meant to be an asynchronous operation that allows initalized debuggers to emit custom events when they receive messages from the debugger

Errors

data ErrorMessage Source #

Instances

Instances details
ToJSON ErrorMessage Source # 
Instance details

Defined in DAP.Types

IsString ErrorMessage Source # 
Instance details

Defined in DAP.Types

Generic ErrorMessage Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ErrorMessage :: Type -> Type Source #

Show ErrorMessage Source # 
Instance details

Defined in DAP.Types

Eq ErrorMessage Source # 
Instance details

Defined in DAP.Types

MonadError (ErrorMessage, Maybe Message) (Adaptor store) Source # 
Instance details

Defined in DAP.Types

Methods

throwError :: (ErrorMessage, Maybe Message) -> Adaptor store a Source #

catchError :: Adaptor store a -> ((ErrorMessage, Maybe Message) -> Adaptor store a) -> Adaptor store a Source #

type Rep ErrorMessage Source # 
Instance details

Defined in DAP.Types

type Rep ErrorMessage = D1 ('MetaData "ErrorMessage" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ErrorMessageCancelled" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorMessageNotStopped" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

newtype ErrorResponse Source #

On error (whenever success is false), the body can provide more details.

Instances

Instances details
ToJSON ErrorResponse Source # 
Instance details

Defined in DAP.Types

Generic ErrorResponse Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ErrorResponse :: Type -> Type Source #

Show ErrorResponse Source # 
Instance details

Defined in DAP.Types

Eq ErrorResponse Source # 
Instance details

Defined in DAP.Types

type Rep ErrorResponse Source # 
Instance details

Defined in DAP.Types

type Rep ErrorResponse = D1 ('MetaData "ErrorResponse" "DAP.Types" "dap-0.1.0.0-inplace" 'True) (C1 ('MetaCons "ErrorResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "errorResponseError") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Message))))

Request

data Request Source #

Constructors

Request 

Fields

Instances

Instances details
FromJSON Request Source # 
Instance details

Defined in DAP.Types

Show Request Source # 
Instance details

Defined in DAP.Types

Misc.

type Seq = Int Source #

Responses

data CompletionsResponse Source #

Constructors

CompletionsResponse 

Fields

data ContinueResponse Source #

Constructors

ContinueResponse 

Fields

  • continueResponseAllThreadsContinued :: Bool

    The value true (or a missing property) signals to the client that all threads have been resumed. The value false indicates that not all threads were resumed.

Instances

Instances details
ToJSON ContinueResponse Source # 
Instance details

Defined in DAP.Types

Generic ContinueResponse Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ContinueResponse :: Type -> Type Source #

Show ContinueResponse Source # 
Instance details

Defined in DAP.Types

Eq ContinueResponse Source # 
Instance details

Defined in DAP.Types

type Rep ContinueResponse Source # 
Instance details

Defined in DAP.Types

type Rep ContinueResponse = D1 ('MetaData "ContinueResponse" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ContinueResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "continueResponseAllThreadsContinued") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data DataBreakpointInfoResponse Source #

Constructors

DataBreakpointInfoResponse 

Fields

Instances

Instances details
ToJSON DataBreakpointInfoResponse Source # 
Instance details

Defined in DAP.Types

Generic DataBreakpointInfoResponse Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep DataBreakpointInfoResponse :: Type -> Type Source #

Show DataBreakpointInfoResponse Source # 
Instance details

Defined in DAP.Types

Eq DataBreakpointInfoResponse Source # 
Instance details

Defined in DAP.Types

type Rep DataBreakpointInfoResponse Source # 
Instance details

Defined in DAP.Types

type Rep DataBreakpointInfoResponse = D1 ('MetaData "DataBreakpointInfoResponse" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "DataBreakpointInfoResponse" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dataBreakpointInfoResponseDataId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "dataBreakpointInfoResponseDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "dataBreakpointInfoResponseDescriptionAccessTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DataBreakpointAccessType]) :*: S1 ('MetaSel ('Just "dataBreakpointInfoResponseDescriptionCanPersist") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))

data DisassembleResponse Source #

Constructors

DisassembleResponse 

Fields

data EvaluateResponse Source #

Constructors

EvaluateResponse 

Fields

Instances

Instances details
ToJSON EvaluateResponse Source # 
Instance details

Defined in DAP.Types

Generic EvaluateResponse Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep EvaluateResponse :: Type -> Type Source #

Show EvaluateResponse Source # 
Instance details

Defined in DAP.Types

Eq EvaluateResponse Source # 
Instance details

Defined in DAP.Types

type Rep EvaluateResponse Source # 
Instance details

Defined in DAP.Types

type Rep EvaluateResponse = D1 ('MetaData "EvaluateResponse" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "EvaluateResponse" 'PrefixI 'True) ((S1 ('MetaSel ('Just "evaluateResponseResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "evaluateResponseType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "evaluateResponsePresentationHint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe VariablePresentationHint)))) :*: ((S1 ('MetaSel ('Just "evaluateResponseVariablesReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "evaluateResponseNamedVariables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "evaluateResponseIndexedVariables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "evaluateResponseMemoryReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))))

data ExceptionInfoResponse Source #

Constructors

ExceptionInfoResponse 

Fields

Instances

Instances details
ToJSON ExceptionInfoResponse Source # 
Instance details

Defined in DAP.Types

Generic ExceptionInfoResponse Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ExceptionInfoResponse :: Type -> Type Source #

Show ExceptionInfoResponse Source # 
Instance details

Defined in DAP.Types

Eq ExceptionInfoResponse Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionInfoResponse Source # 
Instance details

Defined in DAP.Types

type Rep ExceptionInfoResponse = D1 ('MetaData "ExceptionInfoResponse" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ExceptionInfoResponse" 'PrefixI 'True) ((S1 ('MetaSel ('Just "exceptionInfoResponseId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "exceptionInfoDescriptionId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "exceptionInfoBreakMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExceptionBreakMode) :*: S1 ('MetaSel ('Just "exceptionInfoReponseDetails") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExceptionDetails)))))

data GotoTargetsResponse Source #

Constructors

GotoTargetsResponse 

Fields

data ModulesResponse Source #

Constructors

ModulesResponse 

Fields

Instances

Instances details
ToJSON ModulesResponse Source # 
Instance details

Defined in DAP.Types

Generic ModulesResponse Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ModulesResponse :: Type -> Type Source #

Show ModulesResponse Source # 
Instance details

Defined in DAP.Types

Eq ModulesResponse Source # 
Instance details

Defined in DAP.Types

type Rep ModulesResponse Source # 
Instance details

Defined in DAP.Types

type Rep ModulesResponse = D1 ('MetaData "ModulesResponse" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ModulesResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "modulesResponseModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Module]) :*: S1 ('MetaSel ('Just "modulesResponseTotalModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))

data ReadMemoryResponse Source #

Constructors

ReadMemoryResponse 

Fields

  • readMemoryResponseBody :: Int

    The address of the first byte of data returned. Treated as a hex value if prefixed with `0x`, or as a decimal value otherwise.

  • readMemoryResponseAddress :: Text

    The number of unreadable bytes encountered after the last successfully read byte. This can be used to determine the number of bytes that should be skipped before a subsequent readMemory request succeeds.

  • readMemoryResponseUnreadableBytes :: Maybe Int

    The bytes read from memory, encoded using base64. If the decoded length of `data` is less than the requested count in the original readMemory request, and unreadableBytes is zero or omitted, then the client should assume it's reached the end of readable memory.

  • readMemoryResponseData :: Maybe Text
     

Instances

Instances details
ToJSON ReadMemoryResponse Source # 
Instance details

Defined in DAP.Types

Generic ReadMemoryResponse Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ReadMemoryResponse :: Type -> Type Source #

Show ReadMemoryResponse Source # 
Instance details

Defined in DAP.Types

Eq ReadMemoryResponse Source # 
Instance details

Defined in DAP.Types

type Rep ReadMemoryResponse Source # 
Instance details

Defined in DAP.Types

type Rep ReadMemoryResponse = D1 ('MetaData "ReadMemoryResponse" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ReadMemoryResponse" 'PrefixI 'True) ((S1 ('MetaSel ('Just "readMemoryResponseBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "readMemoryResponseAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "readMemoryResponseUnreadableBytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "readMemoryResponseData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

newtype ScopesResponse Source #

Constructors

ScopesResponse 

Fields

  • scopes :: [Scope]

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

data SetExpressionResponse Source #

Constructors

SetExpressionResponse 

Fields

Instances

Instances details
ToJSON SetExpressionResponse Source # 
Instance details

Defined in DAP.Types

Generic SetExpressionResponse Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep SetExpressionResponse :: Type -> Type Source #

Show SetExpressionResponse Source # 
Instance details

Defined in DAP.Types

Eq SetExpressionResponse Source # 
Instance details

Defined in DAP.Types

type Rep SetExpressionResponse Source # 
Instance details

Defined in DAP.Types

type Rep SetExpressionResponse = D1 ('MetaData "SetExpressionResponse" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SetExpressionResponse" 'PrefixI 'True) ((S1 ('MetaSel ('Just "setExpressionResponseValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "setExpressionResponseType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "setExpressionResponsePresentationHint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe VariablePresentationHint)))) :*: (S1 ('MetaSel ('Just "setExpressionResponseVariablesReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "setExpressionResponseNamedVariables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "setExpressionResponseIndexedVariables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))))

data SetVariableResponse Source #

Constructors

SetVariableResponse 

Fields

  • setVariableResponseValue :: Text

    The new value of the variable.

  • setVariableResponseType :: Maybe Text

    The type of the new value. Typically shown in the UI when hovering over the value.

  • setVariableResponseReference :: Maybe Int

    If variablesReference is > 0, the new value is structured and its children can be retrieved by passing variablesReference to the variables request as long as execution remains suspended. See 'Lifetime of Object References' in the Overview section for details.

  • setVariableResponseNamedVariables :: Maybe Int

    The number of named child variables. The client can use this information to present the variables in a paged UI and fetch them in chunks. The value should be less than or equal to 2147483647 (2^31-1).

  • setVariableResponseIndexedVariables :: Maybe Int

    The number of indexed child variables. The client can use this information to present the variables in a paged UI and fetch them in chunks. The value should be less than or equal to 2147483647 (2^31-1).

data SourceResponse Source #

Constructors

SourceResponse 

Fields

data StackTraceResponse Source #

Constructors

StackTraceResponse 

Fields

  • stackFrames :: [StackFrame]

    The frames of the stack frame. If the array has length zero, there are no stack frames available. This means that there is no location information available.

  • totalFrames :: Maybe Int

    The total number of frames available in the stack. If omitted or if totalFrames is larger than the available frames, a client is expected to request frames until a request returns less frames than requested (which indicates the end of the stack). Returning monotonically increasing totalFrames values for subsequent requests can be used to enforce paging in the client.

data StepInTargetsResponse Source #

Constructors

StepInTargetsResponse 

Fields

data VariablesResponse Source #

Constructors

VariablesResponse 

Fields

  • variables :: [Variable]

    All (or a range) of variables for the given variable reference.

data WriteMemoryResponse Source #

Constructors

WriteMemoryResponse 

Fields

  • writeMemoryResponseOffset :: Maybe Int

    Property that should be returned when allowPartial is true to indicate the offset of the first byte of data successfully written. Can be negative.

  • writeMemoryResponseBytesWritten :: Maybe Int

    Property that should be returned when allowPartial is true to indicate the number of bytes starting from address that were successfully written.

Instances

Instances details
ToJSON WriteMemoryResponse Source # 
Instance details

Defined in DAP.Types

Generic WriteMemoryResponse Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep WriteMemoryResponse :: Type -> Type Source #

Show WriteMemoryResponse Source # 
Instance details

Defined in DAP.Types

Eq WriteMemoryResponse Source # 
Instance details

Defined in DAP.Types

type Rep WriteMemoryResponse Source # 
Instance details

Defined in DAP.Types

type Rep WriteMemoryResponse = D1 ('MetaData "WriteMemoryResponse" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "WriteMemoryResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "writeMemoryResponseOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "writeMemoryResponseBytesWritten") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))

Arguments

data AttachRequestArguments Source #

Constructors

AttachRequestArguments 

Fields

  • attachRequestArgumentsRestart :: Maybe Value

    Arbitrary data from the previous, restarted session. The data is sent as the restart attribute of the terminated event. The client should leave the data intact.

data BreakpointLocationsArguments Source #

Constructors

BreakpointLocationsArguments 

Fields

Instances

Instances details
FromJSON BreakpointLocationsArguments Source # 
Instance details

Defined in DAP.Types

Generic BreakpointLocationsArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep BreakpointLocationsArguments :: Type -> Type Source #

Show BreakpointLocationsArguments Source # 
Instance details

Defined in DAP.Types

Eq BreakpointLocationsArguments Source # 
Instance details

Defined in DAP.Types

type Rep BreakpointLocationsArguments Source # 
Instance details

Defined in DAP.Types

type Rep BreakpointLocationsArguments = D1 ('MetaData "BreakpointLocationsArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "BreakpointLocationsArguments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "breakpointLocationsArgumentsSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Source) :*: S1 ('MetaSel ('Just "breakpointLocationsArgumentsLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "breakpointLocationsArgumentsColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "breakpointLocationsArgumentsEndLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "breakpointLocationsArgumentsEndColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))))

data CompletionsArguments Source #

Constructors

CompletionsArguments 

Fields

Instances

Instances details
FromJSON CompletionsArguments Source # 
Instance details

Defined in DAP.Types

Generic CompletionsArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep CompletionsArguments :: Type -> Type Source #

Show CompletionsArguments Source # 
Instance details

Defined in DAP.Types

Eq CompletionsArguments Source # 
Instance details

Defined in DAP.Types

type Rep CompletionsArguments Source # 
Instance details

Defined in DAP.Types

type Rep CompletionsArguments = D1 ('MetaData "CompletionsArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "CompletionsArguments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "completionsArgumentsFrameId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "completionsArgumentsText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "completionsArgumentsColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "completionsArgumentsLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))

data ContinueArguments Source #

Constructors

ContinueArguments 

Fields

Instances

Instances details
FromJSON ContinueArguments Source # 
Instance details

Defined in DAP.Types

Generic ContinueArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ContinueArguments :: Type -> Type Source #

Show ContinueArguments Source # 
Instance details

Defined in DAP.Types

Eq ContinueArguments Source # 
Instance details

Defined in DAP.Types

type Rep ContinueArguments Source # 
Instance details

Defined in DAP.Types

type Rep ContinueArguments = D1 ('MetaData "ContinueArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ContinueArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "continueArgumentsThreadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "continueArgumentsSingleThread") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data DataBreakpointInfoArguments Source #

Constructors

DataBreakpointInfoArguments 

Fields

  • dataBreakpointInfoArgumentsVariablesReference :: Maybe Int

    Reference to the variable container if the data breakpoint is requested for a child of the container. The variablesReference must have been obtained in the current suspended state. See 'Lifetime of Object References' in the Overview section for details.

  • dataBreakpointInfoArgumentsName :: Text

    The name of the variable's child to obtain data breakpoint information for. If variablesReference isn't specified, this can be an expression.

  • dataBreakpointInfoArgumentsFrameId :: Maybe Int

    When name is an expression, evaluate it in the scope of this stack frame. If not specified, the expression is evaluated in the global scope. When variablesReference is specified, this property has no effect.

Instances

Instances details
FromJSON DataBreakpointInfoArguments Source # 
Instance details

Defined in DAP.Types

Generic DataBreakpointInfoArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep DataBreakpointInfoArguments :: Type -> Type Source #

Show DataBreakpointInfoArguments Source # 
Instance details

Defined in DAP.Types

Eq DataBreakpointInfoArguments Source # 
Instance details

Defined in DAP.Types

type Rep DataBreakpointInfoArguments Source # 
Instance details

Defined in DAP.Types

type Rep DataBreakpointInfoArguments = D1 ('MetaData "DataBreakpointInfoArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "DataBreakpointInfoArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "dataBreakpointInfoArgumentsVariablesReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "dataBreakpointInfoArgumentsName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "dataBreakpointInfoArgumentsFrameId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))

data DisassembleArguments Source #

Constructors

DisassembleArguments 

Fields

Instances

Instances details
FromJSON DisassembleArguments Source # 
Instance details

Defined in DAP.Types

Generic DisassembleArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep DisassembleArguments :: Type -> Type Source #

Show DisassembleArguments Source # 
Instance details

Defined in DAP.Types

Eq DisassembleArguments Source # 
Instance details

Defined in DAP.Types

type Rep DisassembleArguments Source # 
Instance details

Defined in DAP.Types

type Rep DisassembleArguments = D1 ('MetaData "DisassembleArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "DisassembleArguments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "disassembleArgumentsMemoryReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "disassembleArgumentsOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "disassembleArgumentsInstructionOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "disassembleArgumentsInstructionCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "disassembleArgumentsResolveSymbols") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))

data DisconnectArguments Source #

Constructors

DisconnectArguments 

Fields

Instances

Instances details
FromJSON DisconnectArguments Source # 
Instance details

Defined in DAP.Types

Generic DisconnectArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep DisconnectArguments :: Type -> Type Source #

Show DisconnectArguments Source # 
Instance details

Defined in DAP.Types

Eq DisconnectArguments Source # 
Instance details

Defined in DAP.Types

type Rep DisconnectArguments Source # 
Instance details

Defined in DAP.Types

type Rep DisconnectArguments = D1 ('MetaData "DisconnectArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "DisconnectArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "disconnectArgumentsRestart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "disconnectArgumentsTerminateDebuggee") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "disconnectArgumentsSuspendDebuggee") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

data EvaluateArguments Source #

Constructors

EvaluateArguments 

Fields

Instances

Instances details
FromJSON EvaluateArguments Source # 
Instance details

Defined in DAP.Types

Generic EvaluateArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep EvaluateArguments :: Type -> Type Source #

Show EvaluateArguments Source # 
Instance details

Defined in DAP.Types

Eq EvaluateArguments Source # 
Instance details

Defined in DAP.Types

type Rep EvaluateArguments Source # 
Instance details

Defined in DAP.Types

type Rep EvaluateArguments = D1 ('MetaData "EvaluateArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "EvaluateArguments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "evaluateArgumentsExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "evaluateArgumentsFrameId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "evaluateArgumentsContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EvaluateArgumentsContext)) :*: S1 ('MetaSel ('Just "evaluateArgumentsFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ValueFormat)))))

data ExceptionInfoArguments Source #

Constructors

ExceptionInfoArguments 

Fields

data GotoArguments Source #

Constructors

GotoArguments 

Fields

Instances

Instances details
FromJSON GotoArguments Source # 
Instance details

Defined in DAP.Types

Generic GotoArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep GotoArguments :: Type -> Type Source #

Show GotoArguments Source # 
Instance details

Defined in DAP.Types

Eq GotoArguments Source # 
Instance details

Defined in DAP.Types

type Rep GotoArguments Source # 
Instance details

Defined in DAP.Types

type Rep GotoArguments = D1 ('MetaData "GotoArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "GotoArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "gotoArgumentsThreadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "gotoArgumentsTargetId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data GotoTargetsArguments Source #

Constructors

GotoTargetsArguments 

Fields

Instances

Instances details
FromJSON GotoTargetsArguments Source # 
Instance details

Defined in DAP.Types

Generic GotoTargetsArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep GotoTargetsArguments :: Type -> Type Source #

Show GotoTargetsArguments Source # 
Instance details

Defined in DAP.Types

Eq GotoTargetsArguments Source # 
Instance details

Defined in DAP.Types

type Rep GotoTargetsArguments Source # 
Instance details

Defined in DAP.Types

type Rep GotoTargetsArguments = D1 ('MetaData "GotoTargetsArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "GotoTargetsArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "gotoTargetsArgumentsSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Source) :*: (S1 ('MetaSel ('Just "gotoTargetsArgumentsLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "gotoTargetsArgumentsColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))

data InitializeRequestArguments Source #

Constructors

InitializeRequestArguments 

Fields

Instances

Instances details
FromJSON InitializeRequestArguments Source # 
Instance details

Defined in DAP.Types

Generic InitializeRequestArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep InitializeRequestArguments :: Type -> Type Source #

Show InitializeRequestArguments Source # 
Instance details

Defined in DAP.Types

Eq InitializeRequestArguments Source # 
Instance details

Defined in DAP.Types

type Rep InitializeRequestArguments Source # 
Instance details

Defined in DAP.Types

type Rep InitializeRequestArguments = D1 ('MetaData "InitializeRequestArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "InitializeRequestArguments" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "clientID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "clientName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "adapterID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "locale") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: ((S1 ('MetaSel ('Just "linesStartAt1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "columnsStartAt1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "pathFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PathFormat)) :*: S1 ('MetaSel ('Just "supportsVariableType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: (((S1 ('MetaSel ('Just "supportsVariablePaging") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsRunInTerminalRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "supportsMemoryReferences") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsProgressReporting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "supportsInvalidatedEvent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsMemoryEvent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "supportsArgsCanBeInterpretedByShell") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "supportsStartDebuggingRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))))

data LaunchRequestArguments Source #

Constructors

LaunchRequestArguments 

Fields

Instances

Instances details
FromJSON LaunchRequestArguments Source # 
Instance details

Defined in DAP.Types

Generic LaunchRequestArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep LaunchRequestArguments :: Type -> Type Source #

Show LaunchRequestArguments Source # 
Instance details

Defined in DAP.Types

Eq LaunchRequestArguments Source # 
Instance details

Defined in DAP.Types

type Rep LaunchRequestArguments Source # 
Instance details

Defined in DAP.Types

type Rep LaunchRequestArguments = D1 ('MetaData "LaunchRequestArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LaunchRequestArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "launchRequestArgumentsNoDebug") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "launchRequestArgumentsRestart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value))))

data ModulesArguments Source #

Constructors

ModulesArguments 

Fields

Instances

Instances details
Generic ModulesArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ModulesArguments :: Type -> Type Source #

Show ModulesArguments Source # 
Instance details

Defined in DAP.Types

Eq ModulesArguments Source # 
Instance details

Defined in DAP.Types

type Rep ModulesArguments Source # 
Instance details

Defined in DAP.Types

type Rep ModulesArguments = D1 ('MetaData "ModulesArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ModulesArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "modulesArgumentsStartModule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "modulesArgumentsModuleCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))

data NextArguments Source #

Constructors

NextArguments 

Fields

Instances

Instances details
FromJSON NextArguments Source # 
Instance details

Defined in DAP.Types

Generic NextArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep NextArguments :: Type -> Type Source #

Show NextArguments Source # 
Instance details

Defined in DAP.Types

Eq NextArguments Source # 
Instance details

Defined in DAP.Types

type Rep NextArguments Source # 
Instance details

Defined in DAP.Types

type Rep NextArguments = D1 ('MetaData "NextArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "NextArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "nextArgumentsThreadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "nextArgumentsSingleThread") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "nextArgumentsGranularity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SteppingGranularity)))))

data PauseArguments Source #

Constructors

PauseArguments 

Fields

Instances

Instances details
FromJSON PauseArguments Source # 
Instance details

Defined in DAP.Types

Generic PauseArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep PauseArguments :: Type -> Type Source #

Show PauseArguments Source # 
Instance details

Defined in DAP.Types

Eq PauseArguments Source # 
Instance details

Defined in DAP.Types

type Rep PauseArguments Source # 
Instance details

Defined in DAP.Types

type Rep PauseArguments = D1 ('MetaData "PauseArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "PauseArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "pauseArgumentsThreadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data ReadMemoryArguments Source #

Constructors

ReadMemoryArguments 

Fields

Instances

Instances details
FromJSON ReadMemoryArguments Source # 
Instance details

Defined in DAP.Types

Generic ReadMemoryArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ReadMemoryArguments :: Type -> Type Source #

Show ReadMemoryArguments Source # 
Instance details

Defined in DAP.Types

Eq ReadMemoryArguments Source # 
Instance details

Defined in DAP.Types

type Rep ReadMemoryArguments Source # 
Instance details

Defined in DAP.Types

type Rep ReadMemoryArguments = D1 ('MetaData "ReadMemoryArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ReadMemoryArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "readMemoryArgumentsmemoryReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "readMemoryArgumentsOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "readMemoryArgumentsCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

data RestartArguments Source #

Constructors

RestartArguments 

Fields

Instances

Instances details
FromJSON RestartArguments Source # 
Instance details

Defined in DAP.Types

Generic RestartArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep RestartArguments :: Type -> Type Source #

Show RestartArguments Source # 
Instance details

Defined in DAP.Types

Eq RestartArguments Source # 
Instance details

Defined in DAP.Types

type Rep RestartArguments Source # 
Instance details

Defined in DAP.Types

type Rep RestartArguments = D1 ('MetaData "RestartArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "RestartArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "restartArgumentsArguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Either LaunchRequestArguments AttachRequestArguments)))))

data RestartFrameArguments Source #

Constructors

RestartFrameArguments 

Fields

  • restartFrameArgumentsFrameId :: Int

    Restart the stack frame identified by frameId. The frameId must have been obtained in the current suspended state. See 'Lifetime of Object References' in the Overview section for details.

data ReverseContinueArguments Source #

Constructors

ReverseContinueArguments 

Fields

Instances

Instances details
FromJSON ReverseContinueArguments Source # 
Instance details

Defined in DAP.Types

Generic ReverseContinueArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ReverseContinueArguments :: Type -> Type Source #

Show ReverseContinueArguments Source # 
Instance details

Defined in DAP.Types

Eq ReverseContinueArguments Source # 
Instance details

Defined in DAP.Types

type Rep ReverseContinueArguments Source # 
Instance details

Defined in DAP.Types

type Rep ReverseContinueArguments = D1 ('MetaData "ReverseContinueArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ReverseContinueArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "reverseContinueArgumentsThreadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "reverseContinueArgumentsSingleThread") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data ScopesArguments Source #

Constructors

ScopesArguments 

Fields

  • scopesArgumentsFrameId :: Int

    Retrieve the scopes for the stack frame identified by frameId. The frameId must have been obtained in the current suspended state. See 'Lifetime of Object References' in the Overview section for details.

Instances

Instances details
FromJSON ScopesArguments Source # 
Instance details

Defined in DAP.Types

Generic ScopesArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep ScopesArguments :: Type -> Type Source #

Show ScopesArguments Source # 
Instance details

Defined in DAP.Types

Eq ScopesArguments Source # 
Instance details

Defined in DAP.Types

type Rep ScopesArguments Source # 
Instance details

Defined in DAP.Types

type Rep ScopesArguments = D1 ('MetaData "ScopesArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ScopesArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "scopesArgumentsFrameId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data SetBreakpointsArguments Source #

Constructors

SetBreakpointsArguments 

Fields

Instances

Instances details
FromJSON SetBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Generic SetBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep SetBreakpointsArguments :: Type -> Type Source #

Show SetBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Eq SetBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetBreakpointsArguments = D1 ('MetaData "SetBreakpointsArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SetBreakpointsArguments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "setBreakpointsArgumentsSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Source) :*: S1 ('MetaSel ('Just "setBreakpointsArgumentsBreakpoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [SourceBreakpoint]))) :*: (S1 ('MetaSel ('Just "setBreakpointsArgumentsLines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Int])) :*: S1 ('MetaSel ('Just "setBreakpointsArgumentsSourceModified") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

data SetDataBreakpointsArguments Source #

Constructors

SetDataBreakpointsArguments 

Fields

Instances

Instances details
FromJSON SetDataBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Generic SetDataBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep SetDataBreakpointsArguments :: Type -> Type Source #

Show SetDataBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Eq SetDataBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetDataBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetDataBreakpointsArguments = D1 ('MetaData "SetDataBreakpointsArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SetDataBreakpointsArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "setDataBreakpointsArgumentsBreakpoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DataBreakpoint])))

data SetExceptionBreakpointsArguments Source #

Constructors

SetExceptionBreakpointsArguments 

Fields

Instances

Instances details
FromJSON SetExceptionBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Generic SetExceptionBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Show SetExceptionBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Eq SetExceptionBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetExceptionBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetExceptionBreakpointsArguments = D1 ('MetaData "SetExceptionBreakpointsArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SetExceptionBreakpointsArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "setExceptionBreakpointsArgumentsFilters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: (S1 ('MetaSel ('Just "setExceptionBreakpointsArgumentsFilterOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExceptionFilterOptions)) :*: S1 ('MetaSel ('Just "setExceptionBreakpointsArgumentsExceptionOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExceptionOptions)))))

data SetExpressionArguments Source #

Constructors

SetExpressionArguments 

Fields

Instances

Instances details
FromJSON SetExpressionArguments Source # 
Instance details

Defined in DAP.Types

Generic SetExpressionArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep SetExpressionArguments :: Type -> Type Source #

Show SetExpressionArguments Source # 
Instance details

Defined in DAP.Types

Eq SetExpressionArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetExpressionArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetExpressionArguments = D1 ('MetaData "SetExpressionArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SetExpressionArguments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "setExpressionArgumentsExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "setExpressionArgumentsValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "setExpressionArgumentsFrameId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "setExpressionArgumentsFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ValueFormat)))))

data SetFunctionBreakpointsArguments Source #

Constructors

SetFunctionBreakpointsArguments 

Fields

Instances

Instances details
FromJSON SetFunctionBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Generic SetFunctionBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Show SetFunctionBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

Eq SetFunctionBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetFunctionBreakpointsArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetFunctionBreakpointsArguments = D1 ('MetaData "SetFunctionBreakpointsArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SetFunctionBreakpointsArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "setFunctionBreakpointsArgumentsBreakpoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FunctionBreakpoint])))

data SetVariableArguments Source #

Constructors

SetVariableArguments 

Fields

Instances

Instances details
FromJSON SetVariableArguments Source # 
Instance details

Defined in DAP.Types

Generic SetVariableArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep SetVariableArguments :: Type -> Type Source #

Show SetVariableArguments Source # 
Instance details

Defined in DAP.Types

Eq SetVariableArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetVariableArguments Source # 
Instance details

Defined in DAP.Types

type Rep SetVariableArguments = D1 ('MetaData "SetVariableArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SetVariableArguments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "setVariableArgumentsVariablesReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "setVariableArgumentsName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "setVariableArgumentsValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "setVariableArgumentsFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ValueFormat)))))

data SourceArguments Source #

Constructors

SourceArguments 

Fields

  • sourceArgumentsSource :: Maybe Source

    Specifies the source content to load. Either `source.path` or `source.sourceReference` must be specified.

  • sourceArgumentsSourceReference :: Int

    The reference to the source. This is the same as `source.sourceReference`. This is provided for backward compatibility since old clients do not understand the source attribute.

Instances

Instances details
FromJSON SourceArguments Source # 
Instance details

Defined in DAP.Types

Generic SourceArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep SourceArguments :: Type -> Type Source #

Show SourceArguments Source # 
Instance details

Defined in DAP.Types

Eq SourceArguments Source # 
Instance details

Defined in DAP.Types

type Rep SourceArguments Source # 
Instance details

Defined in DAP.Types

type Rep SourceArguments = D1 ('MetaData "SourceArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SourceArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceArgumentsSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Source)) :*: S1 ('MetaSel ('Just "sourceArgumentsSourceReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data StackTraceArguments Source #

Constructors

StackTraceArguments 

Fields

Instances

Instances details
FromJSON StackTraceArguments Source # 
Instance details

Defined in DAP.Types

Generic StackTraceArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep StackTraceArguments :: Type -> Type Source #

Show StackTraceArguments Source # 
Instance details

Defined in DAP.Types

Eq StackTraceArguments Source # 
Instance details

Defined in DAP.Types

type Rep StackTraceArguments Source # 
Instance details

Defined in DAP.Types

type Rep StackTraceArguments = D1 ('MetaData "StackTraceArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "StackTraceArguments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "stackTraceArgumentsThreadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "stackTraceArgumentsStartFrame") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "stackTraceArgumentsLevels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "stackTraceArgumentsFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StackFrameFormat)))))

data StepBackArguments Source #

Constructors

StepBackArguments 

Fields

data StepInArguments Source #

Constructors

StepInArguments 

Fields

data StepInTargetsArguments Source #

Constructors

StepInTargetsArguments 

Fields

data StepOutArguments Source #

Constructors

StepOutArguments 

Fields

data TerminateArguments Source #

Constructors

TerminateArguments 

Fields

Instances

Instances details
FromJSON TerminateArguments Source # 
Instance details

Defined in DAP.Types

Generic TerminateArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep TerminateArguments :: Type -> Type Source #

Show TerminateArguments Source # 
Instance details

Defined in DAP.Types

Eq TerminateArguments Source # 
Instance details

Defined in DAP.Types

type Rep TerminateArguments Source # 
Instance details

Defined in DAP.Types

type Rep TerminateArguments = D1 ('MetaData "TerminateArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "TerminateArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "terminateArgumentsRestart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

newtype TerminateThreadsArguments Source #

Constructors

TerminateThreadsArguments 

Fields

data VariablesArguments Source #

Constructors

VariablesArguments 

Fields

data WriteMemoryArguments Source #

Constructors

WriteMemoryArguments 

Fields

  • writeMemoryMemoryReference :: Text

    Memory reference to the base location to which data should be written.

  • writeMemoryArgumentsOffset :: Maybe Int

    Offset (in bytes) to be applied to the reference location before writing data. Can be negative.

  • writeMemoryArgumentsAllowPartial :: Bool

    Property to control partial writes. If true, the debug adapter should attempt to write memory even if the entire memory region is not writable. In such a case the debug adapter should stop after hitting the first byte of memory that cannot be written and return the number of bytes written in the response via the offset and bytesWritten properties. If false or missing, a debug adapter should attempt to verify the region is writable before writing, and fail the response if it is not.

  • writeMemoryArgumentsData :: Text

    Bytes to write, encoded using base64.

Instances

Instances details
FromJSON WriteMemoryArguments Source # 
Instance details

Defined in DAP.Types

Generic WriteMemoryArguments Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep WriteMemoryArguments :: Type -> Type Source #

Show WriteMemoryArguments Source # 
Instance details

Defined in DAP.Types

Eq WriteMemoryArguments Source # 
Instance details

Defined in DAP.Types

type Rep WriteMemoryArguments Source # 
Instance details

Defined in DAP.Types

type Rep WriteMemoryArguments = D1 ('MetaData "WriteMemoryArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "WriteMemoryArguments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "writeMemoryMemoryReference") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "writeMemoryArgumentsOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "writeMemoryArgumentsAllowPartial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "writeMemoryArgumentsData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data RunInTerminalResponse Source #

Constructors

RunInTerminalResponse 

Fields

Instances

Instances details
ToJSON RunInTerminalResponse Source # 
Instance details

Defined in DAP.Types

Generic RunInTerminalResponse Source # 
Instance details

Defined in DAP.Types

Associated Types

type Rep RunInTerminalResponse :: Type -> Type Source #

Show RunInTerminalResponse Source # 
Instance details

Defined in DAP.Types

Eq RunInTerminalResponse Source # 
Instance details

Defined in DAP.Types

type Rep RunInTerminalResponse Source # 
Instance details

Defined in DAP.Types

type Rep RunInTerminalResponse = D1 ('MetaData "RunInTerminalResponse" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "RunInTerminalResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "runInTerminalResponseProcessId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "runInTerminalResponseShellProcessId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))

defaults

Log level

data Level Source #

Constructors

DEBUG 
INFO 
WARN 
ERROR 

Instances

Instances details
Show Level Source # 
Instance details

Defined in DAP.Types

Eq Level Source # 
Instance details

Defined in DAP.Types

Methods

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

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

data DebugStatus Source #

Constructors

SENT 
RECEIVED 

Instances

Instances details
Show DebugStatus Source # 
Instance details

Defined in DAP.Types

Eq DebugStatus Source # 
Instance details

Defined in DAP.Types

Debug Thread state

data DebuggerThreadState Source #

DebuggerThreadState State to hold both the thread that executes the debugger and the thread used to propagate output events from the debugger + debuggee to the editor (via the DAP server).