| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
DAP
Contents
- Message Construction
- Response
- Events
- Server
- Request Arguments
- Debug Session
- Error handling
- Logging
- Internal use
- Internal function used to execute actions on behalf of the DAP server
- Event message API
- Defaults
- Response message API
- Message Type
- Types
- Command
- Event
- Server
- Client
- Errors
- Request
- Misc.
- Responses
- Arguments
- defaults
- Log level
- Debug Thread state
Synopsis
- setBody :: ToJSON value => value -> Adaptor app ()
- setField :: ToJSON value => Key -> value -> Adaptor app ()
- sendSuccesfulEmptyResponse :: Adaptor app ()
- sendSuccesfulResponse :: Adaptor app () -> Adaptor app ()
- sendErrorResponse :: ErrorMessage -> Maybe Message -> Adaptor app ()
- sendSuccesfulEvent :: EventType -> Adaptor app () -> Adaptor app ()
- getServerCapabilities :: Adaptor app Capabilities
- withConnectionLock :: IO () -> Adaptor app ()
- getArguments :: (Show value, FromJSON value) => Adaptor app value
- getRequestSeqNum :: Adaptor app Seq
- registerNewDebugSession :: SessionId -> app -> IO () -> ((Adaptor app () -> IO ()) -> IO ()) -> Adaptor app ()
- updateDebugSession :: (app -> app) -> Adaptor app ()
- getDebugSession :: Adaptor a a
- getDebugSessionId :: Adaptor app SessionId
- destroyDebugSession :: Adaptor app ()
- sendError :: ErrorMessage -> Maybe Message -> Adaptor app a
- logWarn :: ByteString -> Adaptor app ()
- logError :: ByteString -> Adaptor app ()
- logInfo :: ByteString -> Adaptor app ()
- logger :: Level -> SockAddr -> Maybe DebugStatus -> ByteString -> IO ()
- debugMessage :: ByteString -> Adaptor app ()
- send :: Adaptor app () -> Adaptor app ()
- sendRaw :: ToJSON value => value -> Adaptor app ()
- runAdaptorWith :: MVar (AdaptorState app) -> Adaptor app () -> IO ()
- sendBreakpointEvent :: BreakpointEvent -> Adaptor app ()
- sendCapabilitiesEvent :: CapabilitiesEvent -> Adaptor app ()
- sendContinuedEvent :: ContinuedEvent -> Adaptor app ()
- sendExitedEvent :: ExitedEvent -> Adaptor app ()
- sendInitializedEvent :: Adaptor app ()
- sendInvalidatedEvent :: InvalidatedEvent -> Adaptor app ()
- sendLoadedSourceEvent :: LoadedSourceEvent -> Adaptor app ()
- sendMemoryEvent :: MemoryEvent -> Adaptor app ()
- sendModuleEvent :: ModuleEvent -> Adaptor app ()
- sendOutputEvent :: OutputEvent -> Adaptor app ()
- sendProcessEvent :: ProcessEvent -> Adaptor app ()
- sendProgressEndEvent :: ProgressEndEvent -> Adaptor app ()
- sendProgressStartEvent :: ProgressStartEvent -> Adaptor app ()
- sendProgressUpdateEvent :: ProgressUpdateEvent -> Adaptor app ()
- sendStoppedEvent :: StoppedEvent -> Adaptor app ()
- sendTerminatedEvent :: TerminatedEvent -> Adaptor app ()
- sendThreadEvent :: ThreadEvent -> Adaptor app ()
- defaultContinuedEvent :: ContinuedEvent
- defaultExitedEvent :: ExitedEvent
- defaultInvalidatedEvent :: InvalidatedEvent
- defaultMemoryEvent :: MemoryEvent
- defaultOutputEvent :: OutputEvent
- defaultProcessEvent :: ProcessEvent
- defaultProgressEndEvent :: ProgressEndEvent
- defaultProgressStartEvent :: ProgressStartEvent
- defaultProgressUpdateEvent :: ProgressUpdateEvent
- defaultStoppedEvent :: StoppedEvent
- defaultTerminatedEvent :: TerminatedEvent
- defaultThreadEvent :: ThreadEvent
- withLock :: MVar () -> IO () -> IO ()
- withGlobalLock :: IO () -> IO ()
- sendAttachResponse :: Adaptor app ()
- sendBreakpointLocationsResponse :: [BreakpointLocation] -> Adaptor app ()
- sendCompletionsResponse :: CompletionsResponse -> Adaptor app ()
- sendConfigurationDoneResponse :: Adaptor app ()
- sendContinueResponse :: ContinueResponse -> Adaptor app ()
- sendDataBreakpointInfoResponse :: DataBreakpointInfoResponse -> Adaptor app ()
- sendDisassembleResponse :: DisassembleResponse -> Adaptor app ()
- sendDisconnectResponse :: Adaptor app ()
- sendEvaluateResponse :: EvaluateResponse -> Adaptor app ()
- sendExceptionInfoResponse :: ExceptionInfoResponse -> Adaptor app ()
- sendGotoResponse :: Adaptor app ()
- sendGotoTargetsResponse :: Adaptor app ()
- sendInitializeResponse :: Adaptor app ()
- sendLaunchResponse :: Adaptor app ()
- sendLoadedSourcesResponse :: [Source] -> Adaptor app ()
- sendModulesResponse :: ModulesResponse -> Adaptor app ()
- sendNextResponse :: Adaptor app ()
- sendPauseResponse :: Adaptor app ()
- sendReadMemoryResponse :: ReadMemoryResponse -> Adaptor app ()
- sendRestartResponse :: Adaptor app ()
- sendRestartFrameResponse :: Adaptor app ()
- sendReverseContinueResponse :: Adaptor app ()
- sendScopesResponse :: ScopesResponse -> Adaptor app ()
- sendSetBreakpointsResponse :: [Breakpoint] -> Adaptor app ()
- sendSetDataBreakpointsResponse :: [Breakpoint] -> Adaptor app ()
- sendSetExceptionBreakpointsResponse :: [Breakpoint] -> Adaptor app ()
- sendSetExpressionResponse :: SetExpressionResponse -> Adaptor app ()
- sendSetFunctionBreakpointsResponse :: [Breakpoint] -> Adaptor app ()
- sendSetInstructionBreakpointsResponse :: [Breakpoint] -> Adaptor app ()
- sendSetVariableResponse :: SetVariableResponse -> Adaptor app ()
- sendSourceResponse :: SourceResponse -> Adaptor app ()
- sendStackTraceResponse :: StackTraceResponse -> Adaptor app ()
- sendStepBackResponse :: Adaptor app ()
- sendStepInResponse :: Adaptor app ()
- sendStepInTargetsResponse :: StepInTargetsResponse -> Adaptor app ()
- sendStepOutResponse :: Adaptor app ()
- sendTerminateResponse :: Adaptor app ()
- sendTerminateThreadsResponse :: Adaptor app ()
- sendThreadsResponse :: [Thread] -> Adaptor app ()
- sendVariablesResponse :: VariablesResponse -> Adaptor app ()
- sendWriteMemoryResponse :: WriteMemoryResponse -> Adaptor app ()
- sendRunInTerminalResponse :: RunInTerminalResponse -> Adaptor app ()
- sendStartDebuggingResponse :: Adaptor app ()
- runDAPServer :: ServerConfig -> (Command -> Adaptor app ()) -> IO ()
- readPayload :: FromJSON json => Handle -> IO (Either String json)
- data MessageType
- data Breakpoint = Breakpoint {
- breakpointId :: Maybe Int
- breakpointVerified :: Bool
- breakpointMessage :: Maybe Text
- breakpointSource :: Maybe Source
- breakpointLine :: Maybe Int
- breakpointColumn :: Maybe Int
- breakpointEndLine :: Maybe Int
- breakpointEndColumn :: Maybe Int
- breakpointInstructionReference :: Maybe Text
- breakpointOffset :: Maybe Int
- newtype Breakpoints breakpoint = Breakpoints [breakpoint]
- data BreakpointLocation = BreakpointLocation {}
- data Capabilities = Capabilities {
- supportsConfigurationDoneRequest :: Bool
- supportsFunctionBreakpoints :: Bool
- supportsConditionalBreakpoints :: Bool
- supportsHitConditionalBreakpoints :: Bool
- supportsEvaluateForHovers :: Bool
- exceptionBreakpointFilters :: [ExceptionBreakpointsFilter]
- supportsStepBack :: Bool
- supportsSetVariable :: Bool
- supportsRestartFrame :: Bool
- supportsGotoTargetsRequest :: Bool
- supportsStepInTargetsRequest :: Bool
- supportsCompletionsRequest :: Bool
- completionTriggerCharacters :: [Text]
- supportsModulesRequest :: Bool
- additionalModuleColumns :: [ColumnDescriptor]
- supportedChecksumAlgorithms :: [ChecksumAlgorithm]
- supportsRestartRequest :: Bool
- supportsExceptionOptions :: Bool
- supportsValueFormattingOptions :: Bool
- supportsExceptionInfoRequest :: Bool
- supportTerminateDebuggee :: Bool
- supportSuspendDebuggee :: Bool
- supportsDelayedStackTraceLoading :: Bool
- supportsLoadedSourcesRequest :: Bool
- supportsLogPoints :: Bool
- supportsTerminateThreadsRequest :: Bool
- supportsSetExpression :: Bool
- supportsTerminateRequest :: Bool
- supportsDataBreakpoints :: Bool
- supportsReadMemoryRequest :: Bool
- supportsWriteMemoryRequest :: Bool
- supportsDisassembleRequest :: Bool
- supportsCancelRequest :: Bool
- supportsBreakpointLocationsRequest :: Bool
- supportsClipboardContext :: Bool
- supportsSteppingGranularity :: Bool
- supportsInstructionBreakpoints :: Bool
- supportsExceptionFilterOptions :: Bool
- supportsSingleThreadExecutionRequests :: Bool
- data Checksum = Checksum {}
- data ChecksumAlgorithm
- data ColumnDescriptor = ColumnDescriptor {}
- data CompletionItem = CompletionItem {
- completionItemLabel :: String
- completionItemText :: Maybe String
- completionItemSortText :: Maybe String
- completionItemDetail :: Maybe String
- completionItemType :: Maybe CompletionItemType
- completionItemTypeStart :: Maybe Int
- completionItemTypeLength :: Maybe Int
- completionItemTypeSelectionStart :: Maybe Int
- completionItemTypeSelectionLength :: Maybe Int
- data CompletionItemType
- = CompletionItemTypeMethod
- | CompletionItemTypeFunction
- | CompletionItemTypeConstructor
- | CompletionItemTypeField
- | CompletionItemTypeVariable
- | CompletionItemTypeClass
- | CompletionItemTypeInterface
- | CompletionItemTypeModule
- | CompletionItemTypeProperty
- | CompletionItemTypeUnit
- | CompletionItemTypeValue
- | CompletionItemTypeEnum
- | CompletionItemTypeKeyword
- | CompletionItemTypeSnippet
- | CompletionItemTypeText
- | CompletionItemTypeColor
- | CompletionItemTypeFile
- | CompletionItemTypeReference
- | CompletionItemTypeCustomcolor
- data DataBreakpoint = DataBreakpoint {}
- data DataBreakpointAccessType
- data DisassembledInstruction = DisassembledInstruction {
- disassembledInstructionAddress :: Text
- disassembledInstructionInstructionBytes :: Maybe Text
- disassembledInstructionInstruction :: Text
- disassembledInstructionSymbol :: Maybe Text
- disassembledInstructionLocation :: Maybe Source
- disassembledInstructionLine :: Maybe Int
- disassembledInstructionColumn :: Maybe Int
- disassembledInstructionEndLine :: Maybe Int
- disassembledInstructionEndColumn :: Maybe Int
- data ExceptionBreakMode
- data ExceptionBreakpointsFilter = ExceptionBreakpointsFilter {}
- data ExceptionDetails = ExceptionDetails {}
- data ExceptionFilterOptions = ExceptionFilterOptions {}
- data ExceptionOptions = ExceptionOptions {}
- data ExceptionPathSegment = ExceptionPathSegment {}
- data FunctionBreakpoint = FunctionBreakpoint {}
- data GotoTarget = GotoTarget {}
- data InstructionBreakpoint = InstructionBreakpoint {}
- data InvalidatedAreas
- data Message = Message {}
- data Module = Module {}
- data ModulesViewDescriptor = ModulesViewDescriptor {}
- data PresentationHint
- data Scope = Scope {
- scopeName :: Text
- scopePresentationHint :: Maybe ScopePresentationHint
- scopeVariablesReference :: Int
- scopeNamedVariables :: Maybe Int
- scopeIndexedVariables :: Maybe Int
- scopeExpensive :: Bool
- scopeSource :: Maybe Source
- scopeLine :: Maybe Int
- scopeColumn :: Maybe Int
- scopeEndLine :: Maybe Int
- scopeEndColumn :: Maybe Int
- data Source = Source {}
- data SourceBreakpoint = SourceBreakpoint {}
- data SourcePresentationHint
- data StackFrame = StackFrame {
- stackFrameId :: Int
- stackFrameName :: Text
- stackFrameSource :: Maybe Source
- stackFrameLine :: Int
- stackFrameColumn :: Int
- stackFrameEndLine :: Maybe Int
- stackFrameEndColumn :: Maybe Int
- stackFrameCanRestart :: Maybe Bool
- stackFrameInstructionPointerReference :: Maybe Text
- stackFrameModuleId :: Maybe (Either Int Text)
- stackFramePresentationHint :: Maybe PresentationHint
- data StackFrameFormat = StackFrameFormat {
- stackFrameFormatParameters :: Maybe Bool
- stackFrameFormatParameterTypes :: Maybe Bool
- stackFrameFormatParameterNames :: Maybe Bool
- stackFrameFormatParameterValues :: Maybe Bool
- stackFrameFormatLine :: Maybe Bool
- stackFrameFormatModule :: Maybe Bool
- stackFrameFormatIncludeAll :: Maybe Bool
- stackFrameFormatHex :: Maybe Bool
- data StepInTarget = StepInTarget {}
- data SteppingGranularity
- data StoppedEventReason
- data Thread = Thread {
- threadId :: Int
- threadName :: Text
- data ThreadEventReason
- data ValueFormat = ValueFormat {}
- data Variable = Variable {
- variableName :: Text
- variableValue :: Text
- variableType :: Maybe Text
- variablePresentationHint :: Maybe VariablePresentationHint
- variableEvaluateName :: Maybe Text
- variableVariablesReference :: Int
- variableNamedVariables :: Maybe Int
- variableIndexedVariables :: Maybe Int
- variableMemoryReference :: Maybe Text
- data VariablePresentationHint = VariablePresentationHint {}
- data ColumnDescriptorType
- data ScopePresentationHint
- data PresentationHintKind
- = PresentationHintKindProperty
- | PresentationHintKindMethod
- | PresentationHintKindClass
- | PresentationHintKindData
- | PresentationHintKindEvent
- | PresentationHintKindBaseClass
- | PresentationHintKindInnerClass
- | PresentationHintKindInterface
- | PresentationHintKindMostDerivedClass
- | PresentationHintKindVirtual
- | PresentationHintKindDataBreakpoint
- | PresentationHintKind Text
- data PresentationHintAttributes
- = PresentationHintAttributesStatic
- | PresentationHintAttributesConstant
- | PresentationHintAttributesReadOnly
- | PresentationHintAttributesRawText
- | PresentationHintAttributesHasObjectId
- | PresentationHintAttributesCanHaveObjectId
- | PresentationHintAttributesHasSideEffects
- | PresentationHintAttributesHasDataBreakpoint
- | PresentationHintAttributes String
- data PresentationHintVisibility
- data EventGroup
- data EventReason
- data StartMethod
- data EvaluateArgumentsContext
- data PathFormat
- = Path
- | URI
- | PathFormat Text
- data Command
- = CommandCancel
- | CommandRunInTerminal
- | CommandStartDebugging
- | CommandInitialize
- | CommandConfigurationDone
- | CommandLaunch
- | CommandAttach
- | CommandRestart
- | CommandDisconnect
- | CommandTerminate
- | CommandBreakpointLocations
- | CommandSetBreakpoints
- | CommandSetFunctionBreakpoints
- | CommandSetExceptionBreakpoints
- | CommandDataBreakpointInfo
- | CommandSetDataBreakpoints
- | CommandSetInstructionBreakpoints
- | CommandContinue
- | CommandNext
- | CommandStepIn
- | CommandStepOut
- | CommandStepBack
- | CommandReverseContinue
- | CommandRestartFrame
- | CommandGoTo
- | CommandPause
- | CommandStackTrace
- | CommandScopes
- | CommandVariables
- | CommandSetVariable
- | CommandSource
- | CommandThreads
- | CommandTerminateThreads
- | CommandModules
- | CommandLoadedSources
- | CommandEvaluate
- | CommandSetExpression
- | CommandStepInTargets
- | CommandGoToTargets
- | CommandCompletions
- | CommandExceptionInfo
- | CommandReadMemory
- | CommandWriteMemory
- | CommandDisassemble
- | CustomCommand Text
- data EventType
- = EventTypeInitialized
- | EventTypeStopped
- | EventTypeContinued
- | EventTypeExited
- | EventTypeTerminated
- | EventTypeThread
- | EventTypeOutput
- | EventTypeBreakpoint
- | EventTypeModule
- | EventTypeLoadedSource
- | EventTypeProcess
- | EventTypeCapabilities
- | EventTypeProgressStart
- | EventTypeProgressUpdate
- | EventTypeProgressEnd
- | EventTypeInvalidated
- | EventTypeMemory
- data StoppedEvent = StoppedEvent {}
- data ContinuedEvent = ContinuedEvent {}
- data ExitedEvent = ExitedEvent {}
- data TerminatedEvent = TerminatedEvent {}
- data ThreadEvent = ThreadEvent {}
- data OutputEvent = OutputEvent {
- outputEventCategory :: Maybe OutputEventCategory
- outputEventOutput :: Text
- outputEventGroup :: Maybe EventGroup
- outputEventVariablesReference :: Maybe Int
- outputEventSource :: Maybe Source
- outputEventLine :: Maybe Int
- outputEventColumn :: Maybe Int
- outputEventData :: Maybe Value
- data BreakpointEvent = BreakpointEvent {}
- data ModuleEvent = ModuleEvent {}
- data LoadedSourceEvent = LoadedSourceEvent {}
- data ProcessEvent = ProcessEvent {}
- data CapabilitiesEvent = CapabilitiesEvent {}
- data ProgressStartEvent = ProgressStartEvent {}
- data ProgressUpdateEvent = ProgressUpdateEvent {}
- data ProgressEndEvent = ProgressEndEvent {}
- data InvalidatedEvent = InvalidatedEvent {}
- data MemoryEvent = MemoryEvent {}
- data ServerConfig = ServerConfig {
- host :: String
- port :: Int
- serverCapabilities :: Capabilities
- debugLogging :: Bool
- newtype Adaptor store a = Adaptor (ExceptT (ErrorMessage, Maybe Message) (StateT (AdaptorState store) IO) a)
- data AdaptorState app = AdaptorState {
- messageType :: MessageType
- payload :: ![Pair]
- appStore :: AppStore app
- serverConfig :: ServerConfig
- handle :: Handle
- request :: Request
- address :: SockAddr
- sessionId :: Maybe SessionId
- adaptorStateMVar :: MVar (AdaptorState app)
- handleLock :: MVar ()
- type AppStore app = TVar (HashMap SessionId (DebuggerThreadState, app))
- data AdaptorException
- data ErrorMessage
- newtype ErrorResponse = ErrorResponse {}
- data Request = Request {}
- type PayloadSize = Int
- type Seq = Int
- type SessionId = Text
- data CompletionsResponse = CompletionsResponse {}
- data ContinueResponse = ContinueResponse {}
- data DataBreakpointInfoResponse = DataBreakpointInfoResponse {}
- data DisassembleResponse = DisassembleResponse {}
- data EvaluateResponse = EvaluateResponse {}
- data ExceptionInfoResponse = ExceptionInfoResponse {}
- data GotoTargetsResponse = GotoTargetsResponse {}
- data LoadedSourcesResponse = LoadedSourcesResponse {}
- data ModulesResponse = ModulesResponse {}
- data ReadMemoryResponse = ReadMemoryResponse {}
- newtype ScopesResponse = ScopesResponse {}
- data SetExpressionResponse = SetExpressionResponse {}
- data SetVariableResponse = SetVariableResponse {}
- data SourceResponse = SourceResponse {}
- data StackTraceResponse = StackTraceResponse {
- stackFrames :: [StackFrame]
- totalFrames :: Maybe Int
- data StepInTargetsResponse = StepInTargetsResponse {}
- newtype ThreadsResponse = ThreadsResponse {}
- data VariablesResponse = VariablesResponse {}
- data WriteMemoryResponse = WriteMemoryResponse {}
- data AttachRequestArguments = AttachRequestArguments {}
- data BreakpointLocationsArguments = BreakpointLocationsArguments {}
- data CompletionsArguments = CompletionsArguments {}
- data ConfigurationDoneArguments = ConfigurationDoneArguments
- data ContinueArguments = ContinueArguments {}
- data DataBreakpointInfoArguments = DataBreakpointInfoArguments {}
- data DisassembleArguments = DisassembleArguments {}
- data DisconnectArguments = DisconnectArguments {}
- data EvaluateArguments = EvaluateArguments {}
- data ExceptionInfoArguments = ExceptionInfoArguments {}
- data GotoArguments = GotoArguments {}
- data GotoTargetsArguments = GotoTargetsArguments {}
- data InitializeRequestArguments = InitializeRequestArguments {
- clientID :: Maybe Text
- clientName :: Maybe Text
- adapterID :: Text
- locale :: Maybe Text
- linesStartAt1 :: Bool
- columnsStartAt1 :: Bool
- pathFormat :: Maybe PathFormat
- supportsVariableType :: Bool
- supportsVariablePaging :: Bool
- supportsRunInTerminalRequest :: Bool
- supportsMemoryReferences :: Bool
- supportsProgressReporting :: Bool
- supportsInvalidatedEvent :: Bool
- supportsMemoryEvent :: Bool
- supportsArgsCanBeInterpretedByShell :: Bool
- supportsStartDebuggingRequest :: Bool
- data LaunchRequestArguments = LaunchRequestArguments {}
- data LoadedSourcesArguments = LoadedSourcesArguments
- data ModulesArguments = ModulesArguments {}
- data NextArguments = NextArguments {}
- data PauseArguments = PauseArguments {}
- data ReadMemoryArguments = ReadMemoryArguments {}
- data RestartArguments = RestartArguments {}
- data RestartFrameArguments = RestartFrameArguments {}
- data ReverseContinueArguments = ReverseContinueArguments {}
- data ScopesArguments = ScopesArguments {}
- data SetBreakpointsArguments = SetBreakpointsArguments {}
- data SetDataBreakpointsArguments = SetDataBreakpointsArguments {}
- data SetExceptionBreakpointsArguments = SetExceptionBreakpointsArguments {}
- data SetExpressionArguments = SetExpressionArguments {}
- data SetFunctionBreakpointsArguments = SetFunctionBreakpointsArguments {}
- data SetInstructionBreakpointsArguments = SetInstructionBreakpointsArguments {}
- data SetVariableArguments = SetVariableArguments {}
- data SourceArguments = SourceArguments {}
- data StackTraceArguments = StackTraceArguments {}
- data StepBackArguments = StepBackArguments {}
- data StepInArguments = StepInArguments {}
- data StepInTargetsArguments = StepInTargetsArguments {}
- data StepOutArguments = StepOutArguments {}
- data TerminateArguments = TerminateArguments {}
- newtype TerminateThreadsArguments = TerminateThreadsArguments {}
- data ThreadsArguments = ThreadsArguments
- data VariablesArguments = VariablesArguments {}
- data WriteMemoryArguments = WriteMemoryArguments {}
- data RunInTerminalResponse = RunInTerminalResponse {}
- defaultBreakpoint :: Breakpoint
- defaultBreakpointLocation :: BreakpointLocation
- defaultCapabilities :: Capabilities
- defaultColumnDescriptor :: ColumnDescriptor
- defaultCompletionItem :: CompletionItem
- defaultDisassembledInstruction :: DisassembledInstruction
- defaultExceptionBreakpointsFilter :: ExceptionBreakpointsFilter
- defaultExceptionDetails :: ExceptionDetails
- defaultFunctionBreakpoint :: FunctionBreakpoint
- defaultGotoTarget :: GotoTarget
- defaultMessage :: Message
- defaultModule :: Module
- defaultModulesViewDescriptor :: ModulesViewDescriptor
- defaultScope :: Scope
- defaultSource :: Source
- defaultSourceBreakpoint :: SourceBreakpoint
- defaultStackFrame :: StackFrame
- defaultStackFrameFormat :: StackFrameFormat
- defaultStepInTarget :: StepInTarget
- defaultThread :: Thread
- defaultValueFormat :: ValueFormat
- defaultVariable :: Variable
- defaultVariablePresentationHint :: VariablePresentationHint
- data Level
- data DebugStatus
- data DebuggerThreadState = DebuggerThreadState {}
Message Construction
Response
sendSuccesfulEmptyResponse :: Adaptor app () Source #
sendSuccesfulResponse :: Adaptor app () -> Adaptor app () Source #
sendErrorResponse :: ErrorMessage -> Maybe Message -> Adaptor app () Source #
Sends unsuccessful response Only used internally within the Server module
Events
Server
withConnectionLock :: IO () -> Adaptor app () Source #
Request Arguments
getArguments :: (Show value, FromJSON value) => Adaptor app value Source #
Attempt to parse arguments from the Request
getRequestSeqNum :: Adaptor app Seq Source #
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 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 #
getDebugSession :: Adaptor a a Source #
getDebugSessionId :: Adaptor app SessionId 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
logWarn :: ByteString -> Adaptor app () Source #
logError :: ByteString -> Adaptor app () Source #
logInfo :: ByteString -> Adaptor app () Source #
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
sendBreakpointEvent :: BreakpointEvent -> Adaptor app () Source #
sendCapabilitiesEvent :: CapabilitiesEvent -> Adaptor app () Source #
sendContinuedEvent :: ContinuedEvent -> Adaptor app () Source #
sendExitedEvent :: ExitedEvent -> Adaptor app () Source #
sendInitializedEvent :: Adaptor app () Source #
sendInvalidatedEvent :: InvalidatedEvent -> Adaptor app () Source #
sendLoadedSourceEvent :: LoadedSourceEvent -> Adaptor app () Source #
sendMemoryEvent :: MemoryEvent -> Adaptor app () Source #
sendModuleEvent :: ModuleEvent -> Adaptor app () Source #
sendOutputEvent :: OutputEvent -> Adaptor app () Source #
sendProcessEvent :: ProcessEvent -> Adaptor app () Source #
sendProgressEndEvent :: ProgressEndEvent -> Adaptor app () Source #
sendProgressStartEvent :: ProgressStartEvent -> Adaptor app () Source #
sendProgressUpdateEvent :: ProgressUpdateEvent -> Adaptor app () Source #
sendStoppedEvent :: StoppedEvent -> Adaptor app () Source #
sendTerminatedEvent :: TerminatedEvent -> Adaptor app () Source #
sendThreadEvent :: ThreadEvent -> Adaptor app () Source #
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
sendCompletionsResponse :: CompletionsResponse -> Adaptor app () Source #
sendConfigurationDoneResponse :: Adaptor app () Source #
ConfigurationDoneResponse
sendContinueResponse :: ContinueResponse -> Adaptor app () Source #
ContinueResponse
sendDisassembleResponse :: DisassembleResponse -> Adaptor app () Source #
sendDisconnectResponse :: Adaptor app () Source #
DisconnectResponse
sendEvaluateResponse :: EvaluateResponse -> Adaptor app () Source #
sendExceptionInfoResponse :: ExceptionInfoResponse -> Adaptor app () Source #
sendGotoResponse :: Adaptor app () Source #
GotoResponse
sendGotoTargetsResponse :: Adaptor app () Source #
GotoTargetsResponse
sendInitializeResponse :: Adaptor app () Source #
InitializeReponse
sendLaunchResponse :: Adaptor app () Source #
LaunchResponse
sendLoadedSourcesResponse :: [Source] -> Adaptor app () Source #
sendModulesResponse :: ModulesResponse -> Adaptor app () Source #
sendNextResponse :: Adaptor app () Source #
NextResponse
sendPauseResponse :: Adaptor app () Source #
PauseResponse
sendReadMemoryResponse :: ReadMemoryResponse -> Adaptor app () Source #
sendRestartResponse :: Adaptor app () Source #
RestartResponse
sendRestartFrameResponse :: Adaptor app () Source #
RestartFrameResponse
sendReverseContinueResponse :: Adaptor app () Source #
ReverseContinueResponse
sendScopesResponse :: ScopesResponse -> Adaptor app () Source #
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
sendSetExpressionResponse :: SetExpressionResponse -> Adaptor app () Source #
sendSetFunctionBreakpointsResponse :: [Breakpoint] -> Adaptor app () Source #
SetFunctionBreakpointResponse has no body by default
sendSetInstructionBreakpointsResponse :: [Breakpoint] -> Adaptor app () Source #
SetInstructionsBreakpointResponse has no body by default
sendSetVariableResponse :: SetVariableResponse -> Adaptor app () Source #
sendSourceResponse :: SourceResponse -> Adaptor app () Source #
sendStackTraceResponse :: StackTraceResponse -> Adaptor app () Source #
sendStepBackResponse :: Adaptor app () Source #
StepBackResponse
sendStepInResponse :: Adaptor app () Source #
StepInResponse
sendStepInTargetsResponse :: StepInTargetsResponse -> Adaptor app () Source #
sendStepOutResponse :: Adaptor app () Source #
StepOutResponse
sendTerminateResponse :: Adaptor app () Source #
TerminateResponse
sendTerminateThreadsResponse :: Adaptor app () Source #
TerminateThreadsResponse
sendThreadsResponse :: [Thread] -> Adaptor app () Source #
sendVariablesResponse :: VariablesResponse -> Adaptor app () Source #
sendWriteMemoryResponse :: WriteMemoryResponse -> Adaptor app () Source #
sendRunInTerminalResponse :: RunInTerminalResponse -> Adaptor app () Source #
sendStartDebuggingResponse :: Adaptor app () 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 #
Constructors
| MessageTypeEvent | |
| MessageTypeResponse | |
| MessageTypeRequest |
Instances
| ToJSON MessageType Source # | |
Defined in DAP.Types Methods toJSON :: MessageType -> Value Source # toEncoding :: MessageType -> Encoding Source # toJSONList :: [MessageType] -> Value Source # toEncodingList :: [MessageType] -> Encoding Source # | |
| Generic MessageType Source # | |
Defined in DAP.Types Methods from :: MessageType -> Rep MessageType x Source # to :: Rep MessageType x -> MessageType Source # | |
| Show MessageType Source # | |
| Eq MessageType Source # | |
Defined in DAP.Types Methods (==) :: MessageType -> MessageType -> Bool Source # (/=) :: MessageType -> MessageType -> Bool Source # | |
| type Rep MessageType Source # | |
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
newtype Breakpoints breakpoint Source #
Constructors
| Breakpoints [breakpoint] |
Instances
| ToJSON breakpoint => ToJSON (Breakpoints breakpoint) Source # | |
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 # | |
| Eq breakpoint => Eq (Breakpoints breakpoint) Source # | |
Defined in DAP.Types Methods (==) :: Breakpoints breakpoint -> Breakpoints breakpoint -> Bool Source # (/=) :: Breakpoints breakpoint -> Breakpoints breakpoint -> Bool Source # | |
data BreakpointLocation Source #
Constructors
| BreakpointLocation | |
Fields
| |
Instances
data Capabilities Source #
Constructors
| Capabilities | |
Fields
| |
Instances
Constructors
| Checksum | |
Fields
| |
Instances
| FromJSON Checksum Source # | |
| ToJSON Checksum Source # | |
| Generic Checksum Source # | |
| Show Checksum Source # | |
| Eq Checksum Source # | |
| type Rep Checksum Source # | |
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 ChecksumAlgorithm Source #
Instances
| FromJSON ChecksumAlgorithm Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser ChecksumAlgorithm Source # parseJSONList :: Value -> Parser [ChecksumAlgorithm] Source # | |
| ToJSON ChecksumAlgorithm Source # | |
Defined in DAP.Types Methods toJSON :: ChecksumAlgorithm -> Value Source # toEncoding :: ChecksumAlgorithm -> Encoding Source # toJSONList :: [ChecksumAlgorithm] -> Value Source # toEncodingList :: [ChecksumAlgorithm] -> Encoding Source # | |
| Show ChecksumAlgorithm Source # | |
| Eq ChecksumAlgorithm Source # | |
Defined in DAP.Types Methods (==) :: ChecksumAlgorithm -> ChecksumAlgorithm -> Bool Source # (/=) :: ChecksumAlgorithm -> ChecksumAlgorithm -> Bool Source # | |
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
data CompletionItem Source #
Constructors
| CompletionItem | |
Fields
| |
Instances
data CompletionItemType Source #
Constructors
Instances
data DataBreakpoint Source #
Constructors
| DataBreakpoint | |
Fields
| |
Instances
data DataBreakpointAccessType Source #
This enumeration defines all possible access types for data breakpoints. Values: ‘read’, ‘write’, ‘readWrite’
Constructors
| DataBreakpointAccessTypeRead | |
| DataBreakpointAccessTypeWrite | |
| DataBreakpointAccessTypeReadWrite |
Instances
data DisassembledInstruction Source #
Constructors
| DisassembledInstruction | |
Fields
| |
Instances
data ExceptionBreakMode Source #
Constructors
| Never | |
| Always | |
| Unhandled | |
| UserUnhandled |
Instances
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
data ExceptionDetails Source #
Constructors
| ExceptionDetails | |
Fields
| |
Instances
data ExceptionFilterOptions Source #
Constructors
| ExceptionFilterOptions | |
Fields
| |
Instances
data ExceptionOptions Source #
Constructors
| ExceptionOptions | |
Fields
| |
Instances
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.
Constructors
| ExceptionPathSegment | |
Fields | |
Instances
data FunctionBreakpoint Source #
Constructors
| FunctionBreakpoint | |
Fields
| |
Instances
data GotoTarget Source #
Constructors
| GotoTarget | |
Fields
| |
Instances
data InstructionBreakpoint Source #
Constructors
| InstructionBreakpoint | |
Fields
| |
Instances
data InvalidatedAreas Source #
Logical areas that can be invalidated by the invalidated event. Values: https://microsoft.github.io/debug-adapter-protocol/specification#Types_InvalidatedAreas
Constructors
| InvalidatedAreasAll | |
| InvalidatedAreasStacks | |
| InvalidatedAreasThreads | |
| InvalidatedAreasVariables |
Instances
Constructors
| Message | |
Fields
| |
Instances
Constructors
| Module | |
Fields
| |
Instances
data ModulesViewDescriptor Source #
Constructors
| ModulesViewDescriptor | |
Fields | |
Instances
data PresentationHint Source #
Instances
Constructors
| Scope | |
Fields
| |
Instances
Constructors
| Source | |
Fields
| |
Instances
data SourceBreakpoint Source #
Constructors
| SourceBreakpoint | |
Fields
| |
Instances
data SourcePresentationHint Source #
Constructors
| SourcePresentationHintNormal | |
| SourcePresentationHintEmphasize | |
| SourcePresentationHintDeemphasize |
Instances
data StackFrame Source #
Constructors
| StackFrame | |
Fields
| |
Instances
data StackFrameFormat Source #
Constructors
| StackFrameFormat | |
Fields
| |
Instances
data StepInTarget Source #
Constructors
| StepInTarget | |
Fields
| |
Instances
data SteppingGranularity Source #
Instances
data StoppedEventReason Source #
Constructors
Instances
| ToJSON StoppedEventReason Source # | |
Defined in DAP.Types Methods toJSON :: StoppedEventReason -> Value Source # toEncoding :: StoppedEventReason -> Encoding Source # toJSONList :: [StoppedEventReason] -> Value Source # toEncodingList :: [StoppedEventReason] -> Encoding Source # | |
| Show StoppedEventReason Source # | |
| Eq StoppedEventReason Source # | |
Defined in DAP.Types Methods (==) :: StoppedEventReason -> StoppedEventReason -> Bool Source # (/=) :: StoppedEventReason -> StoppedEventReason -> Bool Source # | |
Constructors
| Thread | |
Fields
| |
Instances
| FromJSON Thread Source # | |
| ToJSON Thread Source # | |
| Generic Thread Source # | |
| Show Thread Source # | |
| Eq Thread Source # | |
| type Rep Thread Source # | |
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
data ValueFormat Source #
Constructors
| ValueFormat | |
Fields
| |
Instances
| FromJSON ValueFormat Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser ValueFormat Source # parseJSONList :: Value -> Parser [ValueFormat] Source # | |
| Generic ValueFormat Source # | |
Defined in DAP.Types Methods from :: ValueFormat -> Rep ValueFormat x Source # to :: Rep ValueFormat x -> ValueFormat Source # | |
| Show ValueFormat Source # | |
| Eq ValueFormat Source # | |
Defined in DAP.Types Methods (==) :: ValueFormat -> ValueFormat -> Bool Source # (/=) :: ValueFormat -> ValueFormat -> Bool Source # | |
| type Rep ValueFormat Source # | |
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)))) | |
Constructors
| Variable | |
Fields
| |
Instances
data VariablePresentationHint Source #
Constructors
| VariablePresentationHint | |
Fields
| |
Instances
data ColumnDescriptorType Source #
Constructors
| ColumnDescriptorTypeString | |
| ColumnDescriptorTypeInt | |
| ColumnDescriptorTypeBool | |
| ColumnDescriptorTypeUTCTime UTCTime |
Instances
data ScopePresentationHint Source #
Constructors
| ScopePresentationHintArguments | |
| ScopePresentationHintLocals | |
| ScopePresentationHintRegisters | |
| ScopePresentationHint Text |
Instances
data PresentationHintKind Source #
Constructors
Instances
data PresentationHintAttributes Source #
Constructors
Instances
data PresentationHintVisibility Source #
Constructors
Instances
data EventGroup Source #
Constructors
| EventGroupStart | |
| EventGroupStartCollapsed | |
| EventGroupEnd |
Instances
| ToJSON EventGroup Source # | |
Defined in DAP.Types Methods toJSON :: EventGroup -> Value Source # toEncoding :: EventGroup -> Encoding Source # toJSONList :: [EventGroup] -> Value Source # toEncodingList :: [EventGroup] -> Encoding Source # | |
| Generic EventGroup Source # | |
Defined in DAP.Types | |
| Show EventGroup Source # | |
| Eq EventGroup Source # | |
Defined in DAP.Types Methods (==) :: EventGroup -> EventGroup -> Bool Source # (/=) :: EventGroup -> EventGroup -> Bool Source # | |
| type Rep EventGroup Source # | |
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
data StartMethod Source #
Instances
| ToJSON StartMethod Source # | |
Defined in DAP.Types Methods toJSON :: StartMethod -> Value Source # toEncoding :: StartMethod -> Encoding Source # toJSONList :: [StartMethod] -> Value Source # toEncodingList :: [StartMethod] -> Encoding Source # | |
| Generic StartMethod Source # | |
Defined in DAP.Types Methods from :: StartMethod -> Rep StartMethod x Source # to :: Rep StartMethod x -> StartMethod Source # | |
| Show StartMethod Source # | |
| Eq StartMethod Source # | |
Defined in DAP.Types Methods (==) :: StartMethod -> StartMethod -> Bool Source # (/=) :: StartMethod -> StartMethod -> Bool Source # | |
| type Rep StartMethod Source # | |
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 #
Constructors
| EvaluateArgumentsContextWatch | |
| EvaluateArgumentsContextRepl | |
| EvaluateArgumentsContextHover | |
| EvaluateArgumentsContextClipboard | |
| EvaluateArgumentsContextVariable |
Instances
data PathFormat Source #
Constructors
| Path | |
| URI | |
| PathFormat Text |
Instances
| FromJSON PathFormat Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser PathFormat Source # parseJSONList :: Value -> Parser [PathFormat] Source # | |
| Show PathFormat Source # | |
| Eq PathFormat Source # | |
Defined in DAP.Types Methods (==) :: PathFormat -> PathFormat -> Bool Source # (/=) :: PathFormat -> PathFormat -> Bool Source # | |
Command
Constructors
Instances
| FromJSON Command Source # | |
| ToJSON Command Source # | |
| Generic Command Source # | |
| Read Command Source # | |
| Show Command Source # | |
| Eq Command Source # | |
| type Rep Command Source # | |
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
Constructors
Instances
| ToJSON EventType Source # | |
| Generic EventType Source # | |
| Read EventType Source # | |
| Show EventType Source # | |
| Eq EventType Source # | |
| type Rep EventType Source # | |
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
| |
Instances
data ContinuedEvent Source #
Constructors
| ContinuedEvent | |
Fields
| |
Instances
data ExitedEvent Source #
Constructors
| ExitedEvent | |
Fields
| |
Instances
| ToJSON ExitedEvent Source # | |
Defined in DAP.Types Methods toJSON :: ExitedEvent -> Value Source # toEncoding :: ExitedEvent -> Encoding Source # toJSONList :: [ExitedEvent] -> Value Source # toEncodingList :: [ExitedEvent] -> Encoding Source # | |
| Generic ExitedEvent Source # | |
Defined in DAP.Types Methods from :: ExitedEvent -> Rep ExitedEvent x Source # to :: Rep ExitedEvent x -> ExitedEvent Source # | |
| Show ExitedEvent Source # | |
| Eq ExitedEvent Source # | |
Defined in DAP.Types Methods (==) :: ExitedEvent -> ExitedEvent -> Bool Source # (/=) :: ExitedEvent -> ExitedEvent -> Bool Source # | |
| type Rep ExitedEvent Source # | |
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
| |
Instances
| ToJSON TerminatedEvent Source # | |
Defined in DAP.Types Methods toJSON :: TerminatedEvent -> Value Source # toEncoding :: TerminatedEvent -> Encoding Source # toJSONList :: [TerminatedEvent] -> Value Source # toEncodingList :: [TerminatedEvent] -> Encoding Source # | |
| Generic TerminatedEvent Source # | |
Defined in DAP.Types Methods from :: TerminatedEvent -> Rep TerminatedEvent x Source # to :: Rep TerminatedEvent x -> TerminatedEvent Source # | |
| Show TerminatedEvent Source # | |
| Eq TerminatedEvent Source # | |
Defined in DAP.Types Methods (==) :: TerminatedEvent -> TerminatedEvent -> Bool Source # (/=) :: TerminatedEvent -> TerminatedEvent -> Bool Source # | |
| type Rep TerminatedEvent Source # | |
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
data OutputEvent Source #
Constructors
| OutputEvent | |
Fields
| |
Instances
| ToJSON OutputEvent Source # | |
Defined in DAP.Types Methods toJSON :: OutputEvent -> Value Source # toEncoding :: OutputEvent -> Encoding Source # toJSONList :: [OutputEvent] -> Value Source # toEncodingList :: [OutputEvent] -> Encoding Source # | |
| Generic OutputEvent Source # | |
Defined in DAP.Types Methods from :: OutputEvent -> Rep OutputEvent x Source # to :: Rep OutputEvent x -> OutputEvent Source # | |
| Show OutputEvent Source # | |
| Eq OutputEvent Source # | |
Defined in DAP.Types Methods (==) :: OutputEvent -> OutputEvent -> Bool Source # (/=) :: OutputEvent -> OutputEvent -> Bool Source # | |
| type Rep OutputEvent Source # | |
Defined in DAP.Types | |
data BreakpointEvent Source #
Constructors
| BreakpointEvent | |
Fields
| |
Instances
data ModuleEvent Source #
Constructors
| ModuleEvent | |
Fields
| |
Instances
| ToJSON ModuleEvent Source # | |
Defined in DAP.Types Methods toJSON :: ModuleEvent -> Value Source # toEncoding :: ModuleEvent -> Encoding Source # toJSONList :: [ModuleEvent] -> Value Source # toEncodingList :: [ModuleEvent] -> Encoding Source # | |
| Show ModuleEvent Source # | |
| Eq ModuleEvent Source # | |
Defined in DAP.Types Methods (==) :: ModuleEvent -> ModuleEvent -> Bool Source # (/=) :: ModuleEvent -> ModuleEvent -> Bool Source # | |
data LoadedSourceEvent Source #
Constructors
| LoadedSourceEvent | |
Fields
| |
Instances
| ToJSON LoadedSourceEvent Source # | |
Defined in DAP.Types Methods toJSON :: LoadedSourceEvent -> Value Source # toEncoding :: LoadedSourceEvent -> Encoding Source # toJSONList :: [LoadedSourceEvent] -> Value Source # toEncodingList :: [LoadedSourceEvent] -> Encoding Source # | |
| Show LoadedSourceEvent Source # | |
| Eq LoadedSourceEvent Source # | |
Defined in DAP.Types Methods (==) :: LoadedSourceEvent -> LoadedSourceEvent -> Bool Source # (/=) :: LoadedSourceEvent -> LoadedSourceEvent -> Bool Source # | |
data ProcessEvent Source #
Constructors
| ProcessEvent | |
Fields
| |
Instances
data CapabilitiesEvent Source #
Constructors
| CapabilitiesEvent | |
Fields
| |
Instances
| ToJSON CapabilitiesEvent Source # | |
Defined in DAP.Types Methods toJSON :: CapabilitiesEvent -> Value Source # toEncoding :: CapabilitiesEvent -> Encoding Source # toJSONList :: [CapabilitiesEvent] -> Value Source # toEncodingList :: [CapabilitiesEvent] -> Encoding Source # | |
| Generic CapabilitiesEvent Source # | |
Defined in DAP.Types Methods from :: CapabilitiesEvent -> Rep CapabilitiesEvent x Source # to :: Rep CapabilitiesEvent x -> CapabilitiesEvent Source # | |
| Show CapabilitiesEvent Source # | |
| Eq CapabilitiesEvent Source # | |
Defined in DAP.Types Methods (==) :: CapabilitiesEvent -> CapabilitiesEvent -> Bool Source # (/=) :: CapabilitiesEvent -> CapabilitiesEvent -> Bool Source # | |
| type Rep CapabilitiesEvent Source # | |
Defined in DAP.Types type Rep CapabilitiesEvent = D1 ('MetaData "CapabilitiesEvent" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "CapabilitiesEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "capabilities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Capabilities))) | |
data ProgressStartEvent Source #
Constructors
| ProgressStartEvent | |
Fields
| |
Instances
data ProgressUpdateEvent Source #
Constructors
| ProgressUpdateEvent | |
Fields
| |
Instances
data ProgressEndEvent Source #
Constructors
| ProgressEndEvent | |
Fields
| |
Instances
data InvalidatedEvent Source #
Constructors
| InvalidatedEvent | |
Fields
| |
Instances
data MemoryEvent Source #
Constructors
| MemoryEvent | |
Fields
| |
Instances
Server
data ServerConfig Source #
Constructors
| ServerConfig | |
Fields
| |
Instances
| Show ServerConfig Source # | |
| Eq ServerConfig Source # | |
Defined in DAP.Types Methods (==) :: ServerConfig -> ServerConfig -> Bool Source # (/=) :: ServerConfig -> ServerConfig -> Bool Source # | |
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.
Constructors
| Adaptor (ExceptT (ErrorMessage, Maybe Message) (StateT (AdaptorState store) IO) a) |
Instances
data AdaptorState app Source #
The adaptor state is local to a single connection / thread
Constructors
| AdaptorState | |
Fields
| |
Instances
| MonadState (AdaptorState store) (Adaptor store) Source # | |
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 AdaptorException Source #
Used to signify a malformed message has been received
Constructors
| ParseException String | |
| ExpectedArguments String | |
| DebugSessionIdException String | |
| DebuggerException String |
Instances
| Exception AdaptorException Source # | |
Defined in DAP.Types Methods toException :: AdaptorException -> SomeException Source # fromException :: SomeException -> Maybe AdaptorException Source # | |
| Show AdaptorException Source # | |
| Eq AdaptorException Source # | |
Defined in DAP.Types Methods (==) :: AdaptorException -> AdaptorException -> Bool Source # (/=) :: AdaptorException -> AdaptorException -> Bool Source # | |
data ErrorMessage Source #
Constructors
| ErrorMessageCancelled | |
| ErrorMessageNotStopped | |
| ErrorMessage Text |
Instances
newtype ErrorResponse Source #
On error (whenever success is false), the body can provide more details.
Constructors
| ErrorResponse | |
Fields | |
Instances
| ToJSON ErrorResponse Source # | |
Defined in DAP.Types Methods toJSON :: ErrorResponse -> Value Source # toEncoding :: ErrorResponse -> Encoding Source # toJSONList :: [ErrorResponse] -> Value Source # toEncodingList :: [ErrorResponse] -> Encoding Source # | |
| Generic ErrorResponse Source # | |
Defined in DAP.Types Methods from :: ErrorResponse -> Rep ErrorResponse x Source # to :: Rep ErrorResponse x -> ErrorResponse Source # | |
| Show ErrorResponse Source # | |
| Eq ErrorResponse Source # | |
Defined in DAP.Types Methods (==) :: ErrorResponse -> ErrorResponse -> Bool Source # (/=) :: ErrorResponse -> ErrorResponse -> Bool Source # | |
| type Rep ErrorResponse Source # | |
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
Misc.
type PayloadSize = Int Source #
Responses
data CompletionsResponse Source #
Constructors
| CompletionsResponse | |
Fields
| |
Instances
data ContinueResponse Source #
Constructors
| ContinueResponse | |
Fields
| |
Instances
| ToJSON ContinueResponse Source # | |
Defined in DAP.Types Methods toJSON :: ContinueResponse -> Value Source # toEncoding :: ContinueResponse -> Encoding Source # toJSONList :: [ContinueResponse] -> Value Source # toEncodingList :: [ContinueResponse] -> Encoding Source # | |
| Generic ContinueResponse Source # | |
Defined in DAP.Types Methods from :: ContinueResponse -> Rep ContinueResponse x Source # to :: Rep ContinueResponse x -> ContinueResponse Source # | |
| Show ContinueResponse Source # | |
| Eq ContinueResponse Source # | |
Defined in DAP.Types Methods (==) :: ContinueResponse -> ContinueResponse -> Bool Source # (/=) :: ContinueResponse -> ContinueResponse -> Bool Source # | |
| type Rep ContinueResponse Source # | |
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
data DisassembleResponse Source #
Constructors
| DisassembleResponse | |
Fields
| |
Instances
data EvaluateResponse Source #
Constructors
| EvaluateResponse | |
Fields
| |
Instances
data ExceptionInfoResponse Source #
Constructors
| ExceptionInfoResponse | |
Fields
| |
Instances
data GotoTargetsResponse Source #
Constructors
| GotoTargetsResponse | |
Fields
| |
Instances
data LoadedSourcesResponse Source #
Constructors
| LoadedSourcesResponse | |
Fields
| |
Instances
| ToJSON LoadedSourcesResponse Source # | |
Defined in DAP.Types Methods toJSON :: LoadedSourcesResponse -> Value Source # toEncoding :: LoadedSourcesResponse -> Encoding Source # toJSONList :: [LoadedSourcesResponse] -> Value Source # toEncodingList :: [LoadedSourcesResponse] -> Encoding Source # | |
| Show LoadedSourcesResponse Source # | |
| Eq LoadedSourcesResponse Source # | |
Defined in DAP.Types Methods (==) :: LoadedSourcesResponse -> LoadedSourcesResponse -> Bool Source # (/=) :: LoadedSourcesResponse -> LoadedSourcesResponse -> Bool Source # | |
data ModulesResponse Source #
Constructors
| ModulesResponse | |
Fields
| |
Instances
data ReadMemoryResponse Source #
Constructors
| ReadMemoryResponse | |
Fields
| |
Instances
newtype ScopesResponse Source #
Constructors
| ScopesResponse | |
Instances
| ToJSON ScopesResponse Source # | |
Defined in DAP.Types Methods toJSON :: ScopesResponse -> Value Source # toEncoding :: ScopesResponse -> Encoding Source # toJSONList :: [ScopesResponse] -> Value Source # toEncodingList :: [ScopesResponse] -> Encoding Source # | |
| Show ScopesResponse Source # | |
| Eq ScopesResponse Source # | |
Defined in DAP.Types Methods (==) :: ScopesResponse -> ScopesResponse -> Bool Source # (/=) :: ScopesResponse -> ScopesResponse -> Bool Source # | |
data SetExpressionResponse Source #
Constructors
| SetExpressionResponse | |
Fields
| |
Instances
data SetVariableResponse Source #
Constructors
| SetVariableResponse | |
Fields
| |
Instances
| ToJSON SetVariableResponse Source # | |
Defined in DAP.Types Methods toJSON :: SetVariableResponse -> Value Source # toEncoding :: SetVariableResponse -> Encoding Source # toJSONList :: [SetVariableResponse] -> Value Source # toEncodingList :: [SetVariableResponse] -> Encoding Source # | |
| Show SetVariableResponse Source # | |
| Eq SetVariableResponse Source # | |
Defined in DAP.Types Methods (==) :: SetVariableResponse -> SetVariableResponse -> Bool Source # (/=) :: SetVariableResponse -> SetVariableResponse -> Bool Source # | |
data SourceResponse Source #
Constructors
| SourceResponse | |
Fields
| |
Instances
| ToJSON SourceResponse Source # | |
Defined in DAP.Types Methods toJSON :: SourceResponse -> Value Source # toEncoding :: SourceResponse -> Encoding Source # toJSONList :: [SourceResponse] -> Value Source # toEncodingList :: [SourceResponse] -> Encoding Source # | |
| Show SourceResponse Source # | |
| Eq SourceResponse Source # | |
Defined in DAP.Types Methods (==) :: SourceResponse -> SourceResponse -> Bool Source # (/=) :: SourceResponse -> SourceResponse -> Bool Source # | |
data StackTraceResponse Source #
Constructors
| StackTraceResponse | |
Fields
| |
Instances
| ToJSON StackTraceResponse Source # | |
Defined in DAP.Types Methods toJSON :: StackTraceResponse -> Value Source # toEncoding :: StackTraceResponse -> Encoding Source # toJSONList :: [StackTraceResponse] -> Value Source # toEncodingList :: [StackTraceResponse] -> Encoding Source # | |
| Show StackTraceResponse Source # | |
| Eq StackTraceResponse Source # | |
Defined in DAP.Types Methods (==) :: StackTraceResponse -> StackTraceResponse -> Bool Source # (/=) :: StackTraceResponse -> StackTraceResponse -> Bool Source # | |
data StepInTargetsResponse Source #
Constructors
| StepInTargetsResponse | |
Fields
| |
Instances
newtype ThreadsResponse Source #
Constructors
| ThreadsResponse | |
Instances
| ToJSON ThreadsResponse Source # | |
Defined in DAP.Types Methods toJSON :: ThreadsResponse -> Value Source # toEncoding :: ThreadsResponse -> Encoding Source # toJSONList :: [ThreadsResponse] -> Value Source # toEncodingList :: [ThreadsResponse] -> Encoding Source # | |
| Show ThreadsResponse Source # | |
| Eq ThreadsResponse Source # | |
Defined in DAP.Types Methods (==) :: ThreadsResponse -> ThreadsResponse -> Bool Source # (/=) :: ThreadsResponse -> ThreadsResponse -> Bool Source # | |
data VariablesResponse Source #
Constructors
| VariablesResponse | |
Instances
| ToJSON VariablesResponse Source # | |
Defined in DAP.Types Methods toJSON :: VariablesResponse -> Value Source # toEncoding :: VariablesResponse -> Encoding Source # toJSONList :: [VariablesResponse] -> Value Source # toEncodingList :: [VariablesResponse] -> Encoding Source # | |
| Generic VariablesResponse Source # | |
Defined in DAP.Types Methods from :: VariablesResponse -> Rep VariablesResponse x Source # to :: Rep VariablesResponse x -> VariablesResponse Source # | |
| Show VariablesResponse Source # | |
| Eq VariablesResponse Source # | |
Defined in DAP.Types Methods (==) :: VariablesResponse -> VariablesResponse -> Bool Source # (/=) :: VariablesResponse -> VariablesResponse -> Bool Source # | |
| type Rep VariablesResponse Source # | |
Defined in DAP.Types type Rep VariablesResponse = D1 ('MetaData "VariablesResponse" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "VariablesResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "variables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Variable]))) | |
data WriteMemoryResponse Source #
Constructors
| WriteMemoryResponse | |
Fields
| |
Instances
Arguments
data AttachRequestArguments Source #
Constructors
| AttachRequestArguments | |
Fields
| |
Instances
data BreakpointLocationsArguments Source #
Constructors
| BreakpointLocationsArguments | |
Fields
| |
Instances
data CompletionsArguments Source #
Constructors
| CompletionsArguments | |
Fields
| |
Instances
data ConfigurationDoneArguments Source #
Constructors
| ConfigurationDoneArguments |
Instances
| FromJSON ConfigurationDoneArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser ConfigurationDoneArguments Source # parseJSONList :: Value -> Parser [ConfigurationDoneArguments] Source # | |
| Show ConfigurationDoneArguments Source # | |
| Eq ConfigurationDoneArguments Source # | |
Defined in DAP.Types Methods (==) :: ConfigurationDoneArguments -> ConfigurationDoneArguments -> Bool Source # (/=) :: ConfigurationDoneArguments -> ConfigurationDoneArguments -> Bool Source # | |
data ContinueArguments Source #
Constructors
| ContinueArguments | |
Fields
| |
Instances
data DataBreakpointInfoArguments Source #
Constructors
| DataBreakpointInfoArguments | |
Fields
| |
Instances
data DisassembleArguments Source #
Constructors
| DisassembleArguments | |
Fields
| |
Instances
data DisconnectArguments Source #
Constructors
| DisconnectArguments | |
Fields
| |
Instances
data EvaluateArguments Source #
Constructors
| EvaluateArguments | |
Fields
| |
Instances
data ExceptionInfoArguments Source #
Constructors
| ExceptionInfoArguments | |
Fields
| |
Instances
data GotoArguments Source #
Constructors
| GotoArguments | |
Fields
| |
Instances
| FromJSON GotoArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser GotoArguments Source # parseJSONList :: Value -> Parser [GotoArguments] Source # | |
| Generic GotoArguments Source # | |
Defined in DAP.Types Methods from :: GotoArguments -> Rep GotoArguments x Source # to :: Rep GotoArguments x -> GotoArguments Source # | |
| Show GotoArguments Source # | |
| Eq GotoArguments Source # | |
Defined in DAP.Types Methods (==) :: GotoArguments -> GotoArguments -> Bool Source # (/=) :: GotoArguments -> GotoArguments -> Bool Source # | |
| type Rep GotoArguments Source # | |
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
data InitializeRequestArguments Source #
Constructors
| InitializeRequestArguments | |
Fields
| |
Instances
data LaunchRequestArguments Source #
Constructors
| LaunchRequestArguments | |
Fields
| |
Instances
data LoadedSourcesArguments Source #
Constructors
| LoadedSourcesArguments |
Instances
| FromJSON LoadedSourcesArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser LoadedSourcesArguments Source # parseJSONList :: Value -> Parser [LoadedSourcesArguments] Source # | |
| Show LoadedSourcesArguments Source # | |
| Eq LoadedSourcesArguments Source # | |
Defined in DAP.Types Methods (==) :: LoadedSourcesArguments -> LoadedSourcesArguments -> Bool Source # (/=) :: LoadedSourcesArguments -> LoadedSourcesArguments -> Bool Source # | |
data ModulesArguments Source #
Constructors
| ModulesArguments | |
Fields
| |
Instances
| Generic ModulesArguments Source # | |
Defined in DAP.Types Methods from :: ModulesArguments -> Rep ModulesArguments x Source # to :: Rep ModulesArguments x -> ModulesArguments Source # | |
| Show ModulesArguments Source # | |
| Eq ModulesArguments Source # | |
Defined in DAP.Types Methods (==) :: ModulesArguments -> ModulesArguments -> Bool Source # (/=) :: ModulesArguments -> ModulesArguments -> Bool Source # | |
| type Rep ModulesArguments Source # | |
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
data PauseArguments Source #
Constructors
| PauseArguments | |
Fields
| |
Instances
| FromJSON PauseArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser PauseArguments Source # parseJSONList :: Value -> Parser [PauseArguments] Source # | |
| Generic PauseArguments Source # | |
Defined in DAP.Types Methods from :: PauseArguments -> Rep PauseArguments x Source # to :: Rep PauseArguments x -> PauseArguments Source # | |
| Show PauseArguments Source # | |
| Eq PauseArguments Source # | |
Defined in DAP.Types Methods (==) :: PauseArguments -> PauseArguments -> Bool Source # (/=) :: PauseArguments -> PauseArguments -> Bool Source # | |
| type Rep PauseArguments Source # | |
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
data RestartArguments Source #
Constructors
| RestartArguments | |
Fields
| |
Instances
| FromJSON RestartArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser RestartArguments Source # parseJSONList :: Value -> Parser [RestartArguments] Source # | |
| Generic RestartArguments Source # | |
Defined in DAP.Types Methods from :: RestartArguments -> Rep RestartArguments x Source # to :: Rep RestartArguments x -> RestartArguments Source # | |
| Show RestartArguments Source # | |
| Eq RestartArguments Source # | |
Defined in DAP.Types Methods (==) :: RestartArguments -> RestartArguments -> Bool Source # (/=) :: RestartArguments -> RestartArguments -> Bool Source # | |
| type Rep RestartArguments Source # | |
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
| |
Instances
| FromJSON RestartFrameArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser RestartFrameArguments Source # parseJSONList :: Value -> Parser [RestartFrameArguments] Source # | |
| Generic RestartFrameArguments Source # | |
Defined in DAP.Types Methods from :: RestartFrameArguments -> Rep RestartFrameArguments x Source # to :: Rep RestartFrameArguments x -> RestartFrameArguments Source # | |
| Show RestartFrameArguments Source # | |
| Eq RestartFrameArguments Source # | |
Defined in DAP.Types Methods (==) :: RestartFrameArguments -> RestartFrameArguments -> Bool Source # (/=) :: RestartFrameArguments -> RestartFrameArguments -> Bool Source # | |
| type Rep RestartFrameArguments Source # | |
Defined in DAP.Types type Rep RestartFrameArguments = D1 ('MetaData "RestartFrameArguments" "DAP.Types" "dap-0.1.0.0-inplace" 'False) (C1 ('MetaCons "RestartFrameArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "restartFrameArgumentsFrameId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) | |
data ReverseContinueArguments Source #
Constructors
| ReverseContinueArguments | |
Fields
| |
Instances
data ScopesArguments Source #
Constructors
| ScopesArguments | |
Fields
| |
Instances
| FromJSON ScopesArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser ScopesArguments Source # parseJSONList :: Value -> Parser [ScopesArguments] Source # | |
| Generic ScopesArguments Source # | |
Defined in DAP.Types Methods from :: ScopesArguments -> Rep ScopesArguments x Source # to :: Rep ScopesArguments x -> ScopesArguments Source # | |
| Show ScopesArguments Source # | |
| Eq ScopesArguments Source # | |
Defined in DAP.Types Methods (==) :: ScopesArguments -> ScopesArguments -> Bool Source # (/=) :: ScopesArguments -> ScopesArguments -> Bool Source # | |
| type Rep ScopesArguments Source # | |
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
data SetDataBreakpointsArguments Source #
Constructors
| SetDataBreakpointsArguments | |
Fields
| |
Instances
| FromJSON SetDataBreakpointsArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser SetDataBreakpointsArguments Source # parseJSONList :: Value -> Parser [SetDataBreakpointsArguments] Source # | |
| Generic SetDataBreakpointsArguments Source # | |
Defined in DAP.Types | |
| Show SetDataBreakpointsArguments Source # | |
| Eq SetDataBreakpointsArguments Source # | |
Defined in DAP.Types Methods (==) :: SetDataBreakpointsArguments -> SetDataBreakpointsArguments -> Bool Source # (/=) :: SetDataBreakpointsArguments -> SetDataBreakpointsArguments -> Bool Source # | |
| type Rep SetDataBreakpointsArguments Source # | |
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
data SetExpressionArguments Source #
Constructors
| SetExpressionArguments | |
Fields
| |
Instances
data SetFunctionBreakpointsArguments Source #
Constructors
| SetFunctionBreakpointsArguments | |
Fields
| |
Instances
| FromJSON SetFunctionBreakpointsArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser SetFunctionBreakpointsArguments Source # parseJSONList :: Value -> Parser [SetFunctionBreakpointsArguments] Source # | |
| Generic SetFunctionBreakpointsArguments Source # | |
Defined in DAP.Types | |
| Show SetFunctionBreakpointsArguments Source # | |
| Eq SetFunctionBreakpointsArguments Source # | |
Defined in DAP.Types | |
| type Rep SetFunctionBreakpointsArguments Source # | |
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 SetInstructionBreakpointsArguments Source #
Constructors
| SetInstructionBreakpointsArguments | |
Fields
| |
Instances
data SetVariableArguments Source #
Constructors
| SetVariableArguments | |
Fields
| |
Instances
data SourceArguments Source #
Constructors
| SourceArguments | |
Fields
| |
Instances
data StackTraceArguments Source #
Constructors
| StackTraceArguments | |
Fields
| |
Instances
data StepBackArguments Source #
Constructors
| StepBackArguments | |
Fields
| |
Instances
| Show StepBackArguments Source # | |
| Eq StepBackArguments Source # | |
Defined in DAP.Types Methods (==) :: StepBackArguments -> StepBackArguments -> Bool Source # (/=) :: StepBackArguments -> StepBackArguments -> Bool Source # | |
data StepInArguments Source #
Constructors
| StepInArguments | |
Fields
| |
Instances
| Show StepInArguments Source # | |
| Eq StepInArguments Source # | |
Defined in DAP.Types Methods (==) :: StepInArguments -> StepInArguments -> Bool Source # (/=) :: StepInArguments -> StepInArguments -> Bool Source # | |
data StepInTargetsArguments Source #
Constructors
| StepInTargetsArguments | |
Fields
| |
Instances
data StepOutArguments Source #
Constructors
| StepOutArguments | |
Fields
| |
Instances
| Show StepOutArguments Source # | |
| Eq StepOutArguments Source # | |
Defined in DAP.Types Methods (==) :: StepOutArguments -> StepOutArguments -> Bool Source # (/=) :: StepOutArguments -> StepOutArguments -> Bool Source # | |
data TerminateArguments Source #
Constructors
| TerminateArguments | |
Fields
| |
Instances
| FromJSON TerminateArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser TerminateArguments Source # parseJSONList :: Value -> Parser [TerminateArguments] Source # | |
| Generic TerminateArguments Source # | |
Defined in DAP.Types Methods from :: TerminateArguments -> Rep TerminateArguments x Source # to :: Rep TerminateArguments x -> TerminateArguments Source # | |
| Show TerminateArguments Source # | |
| Eq TerminateArguments Source # | |
Defined in DAP.Types Methods (==) :: TerminateArguments -> TerminateArguments -> Bool Source # (/=) :: TerminateArguments -> TerminateArguments -> Bool Source # | |
| type Rep TerminateArguments Source # | |
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
| |
Instances
data ThreadsArguments Source #
Constructors
| ThreadsArguments |
Instances
| FromJSON ThreadsArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser ThreadsArguments Source # parseJSONList :: Value -> Parser [ThreadsArguments] Source # | |
| Show ThreadsArguments Source # | |
| Eq ThreadsArguments Source # | |
Defined in DAP.Types Methods (==) :: ThreadsArguments -> ThreadsArguments -> Bool Source # (/=) :: ThreadsArguments -> ThreadsArguments -> Bool Source # | |
data VariablesArguments Source #
Constructors
| VariablesArguments | |
Fields
| |
Instances
| FromJSON VariablesArguments Source # | |
Defined in DAP.Types Methods parseJSON :: Value -> Parser VariablesArguments Source # parseJSONList :: Value -> Parser [VariablesArguments] Source # | |
| Generic VariablesArguments Source # | |
Defined in DAP.Types Methods from :: VariablesArguments -> Rep VariablesArguments x Source # to :: Rep VariablesArguments x -> VariablesArguments Source # | |
| Show VariablesArguments Source # | |
| Eq VariablesArguments Source # | |
Defined in DAP.Types Methods (==) :: VariablesArguments -> VariablesArguments -> Bool Source # (/=) :: VariablesArguments -> VariablesArguments -> Bool Source # | |
| type Rep VariablesArguments Source # | |
Defined in DAP.Types | |
data WriteMemoryArguments Source #
Constructors
| WriteMemoryArguments | |
Fields
| |
Instances
data RunInTerminalResponse Source #
Constructors
| RunInTerminalResponse | |
Fields
| |
Instances
defaults
defaultScope :: Scope Source #
Log level
data DebugStatus Source #
Instances
| Show DebugStatus Source # | |
| Eq DebugStatus Source # | |
Defined in DAP.Types Methods (==) :: DebugStatus -> DebugStatus -> Bool Source # (/=) :: DebugStatus -> DebugStatus -> Bool Source # | |
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).
Constructors
| DebuggerThreadState | |
Fields | |