Safe Haskell | None |
---|---|
Language | Haskell2010 |
Debugger
Debugger domain exposes JavaScript debugging capabilities. It allows setting and removing breakpoints, stepping through execution, exploring stack traces, etc.
Synopsis
- data PDebuggerStepOver = PDebuggerStepOver {}
- data PDebuggerStepOut = PDebuggerStepOut
- data PDebuggerStepInto = PDebuggerStepInto {}
- data PDebuggerSetVariableValue = PDebuggerSetVariableValue {}
- data PDebuggerSetSkipAllPauses = PDebuggerSetSkipAllPauses {}
- data DebuggerSetScriptSource = DebuggerSetScriptSource {}
- data DebuggerSetScriptSourceStatus
- data PDebuggerSetScriptSource = PDebuggerSetScriptSource {}
- data PDebuggerSetReturnValue = PDebuggerSetReturnValue {}
- data PDebuggerSetPauseOnExceptions = PDebuggerSetPauseOnExceptions {}
- data PDebuggerSetPauseOnExceptionsState
- data PDebuggerSetBreakpointsActive = PDebuggerSetBreakpointsActive {}
- data DebuggerSetBreakpointOnFunctionCall = DebuggerSetBreakpointOnFunctionCall {}
- data PDebuggerSetBreakpointOnFunctionCall = PDebuggerSetBreakpointOnFunctionCall {}
- data DebuggerSetBreakpointByUrl = DebuggerSetBreakpointByUrl {}
- data PDebuggerSetBreakpointByUrl = PDebuggerSetBreakpointByUrl {}
- data DebuggerSetInstrumentationBreakpoint = DebuggerSetInstrumentationBreakpoint {}
- data PDebuggerSetInstrumentationBreakpoint = PDebuggerSetInstrumentationBreakpoint {}
- data PDebuggerSetInstrumentationBreakpointInstrumentation
- data DebuggerSetBreakpoint = DebuggerSetBreakpoint {}
- data PDebuggerSetBreakpoint = PDebuggerSetBreakpoint {}
- data PDebuggerSetBlackboxedRanges = PDebuggerSetBlackboxedRanges {}
- data PDebuggerSetBlackboxPatterns = PDebuggerSetBlackboxPatterns {}
- data PDebuggerSetAsyncCallStackDepth = PDebuggerSetAsyncCallStackDepth {}
- data DebuggerSearchInContent = DebuggerSearchInContent {}
- data PDebuggerSearchInContent = PDebuggerSearchInContent {}
- data PDebuggerResume = PDebuggerResume {}
- data PDebuggerRestartFrame = PDebuggerRestartFrame {}
- data PDebuggerRestartFrameMode = PDebuggerRestartFrameModeStepInto
- data PDebuggerRemoveBreakpoint = PDebuggerRemoveBreakpoint {}
- data PDebuggerPause = PDebuggerPause
- data DebuggerGetStackTrace = DebuggerGetStackTrace {}
- data PDebuggerGetStackTrace = PDebuggerGetStackTrace {}
- data DebuggerNextWasmDisassemblyChunk = DebuggerNextWasmDisassemblyChunk {}
- data PDebuggerNextWasmDisassemblyChunk = PDebuggerNextWasmDisassemblyChunk {}
- data DebuggerDisassembleWasmModule = DebuggerDisassembleWasmModule {}
- data PDebuggerDisassembleWasmModule = PDebuggerDisassembleWasmModule {}
- data DebuggerGetScriptSource = DebuggerGetScriptSource {}
- data PDebuggerGetScriptSource = PDebuggerGetScriptSource {}
- data DebuggerGetPossibleBreakpoints = DebuggerGetPossibleBreakpoints {}
- data PDebuggerGetPossibleBreakpoints = PDebuggerGetPossibleBreakpoints {}
- data DebuggerEvaluateOnCallFrame = DebuggerEvaluateOnCallFrame {}
- data PDebuggerEvaluateOnCallFrame = PDebuggerEvaluateOnCallFrame {
- pDebuggerEvaluateOnCallFrameCallFrameId :: DebuggerCallFrameId
- pDebuggerEvaluateOnCallFrameExpression :: Text
- pDebuggerEvaluateOnCallFrameObjectGroup :: Maybe Text
- pDebuggerEvaluateOnCallFrameIncludeCommandLineAPI :: Maybe Bool
- pDebuggerEvaluateOnCallFrameSilent :: Maybe Bool
- pDebuggerEvaluateOnCallFrameReturnByValue :: Maybe Bool
- pDebuggerEvaluateOnCallFrameGeneratePreview :: Maybe Bool
- pDebuggerEvaluateOnCallFrameThrowOnSideEffect :: Maybe Bool
- pDebuggerEvaluateOnCallFrameTimeout :: Maybe RuntimeTimeDelta
- data DebuggerEnable = DebuggerEnable {}
- data PDebuggerEnable = PDebuggerEnable {}
- data PDebuggerDisable = PDebuggerDisable
- data PDebuggerContinueToLocation = PDebuggerContinueToLocation {}
- data PDebuggerContinueToLocationTargetCallFrames
- data DebuggerScriptParsed = DebuggerScriptParsed {
- debuggerScriptParsedScriptId :: RuntimeScriptId
- debuggerScriptParsedUrl :: Text
- debuggerScriptParsedStartLine :: Int
- debuggerScriptParsedStartColumn :: Int
- debuggerScriptParsedEndLine :: Int
- debuggerScriptParsedEndColumn :: Int
- debuggerScriptParsedExecutionContextId :: RuntimeExecutionContextId
- debuggerScriptParsedHash :: Text
- debuggerScriptParsedExecutionContextAuxData :: Maybe [(Text, Text)]
- debuggerScriptParsedIsLiveEdit :: Maybe Bool
- debuggerScriptParsedSourceMapURL :: Maybe Text
- debuggerScriptParsedHasSourceURL :: Maybe Bool
- debuggerScriptParsedIsModule :: Maybe Bool
- debuggerScriptParsedLength :: Maybe Int
- debuggerScriptParsedStackTrace :: Maybe RuntimeStackTrace
- debuggerScriptParsedCodeOffset :: Maybe Int
- debuggerScriptParsedScriptLanguage :: Maybe DebuggerScriptLanguage
- debuggerScriptParsedDebugSymbols :: Maybe DebuggerDebugSymbols
- debuggerScriptParsedEmbedderName :: Maybe Text
- data DebuggerScriptFailedToParse = DebuggerScriptFailedToParse {
- debuggerScriptFailedToParseScriptId :: RuntimeScriptId
- debuggerScriptFailedToParseUrl :: Text
- debuggerScriptFailedToParseStartLine :: Int
- debuggerScriptFailedToParseStartColumn :: Int
- debuggerScriptFailedToParseEndLine :: Int
- debuggerScriptFailedToParseEndColumn :: Int
- debuggerScriptFailedToParseExecutionContextId :: RuntimeExecutionContextId
- debuggerScriptFailedToParseHash :: Text
- debuggerScriptFailedToParseExecutionContextAuxData :: Maybe [(Text, Text)]
- debuggerScriptFailedToParseSourceMapURL :: Maybe Text
- debuggerScriptFailedToParseHasSourceURL :: Maybe Bool
- debuggerScriptFailedToParseIsModule :: Maybe Bool
- debuggerScriptFailedToParseLength :: Maybe Int
- debuggerScriptFailedToParseStackTrace :: Maybe RuntimeStackTrace
- debuggerScriptFailedToParseCodeOffset :: Maybe Int
- debuggerScriptFailedToParseScriptLanguage :: Maybe DebuggerScriptLanguage
- debuggerScriptFailedToParseEmbedderName :: Maybe Text
- data DebuggerResumed = DebuggerResumed
- data DebuggerPaused = DebuggerPaused {}
- data DebuggerPausedReason
- = DebuggerPausedReasonAmbiguous
- | DebuggerPausedReasonAssert
- | DebuggerPausedReasonCSPViolation
- | DebuggerPausedReasonDebugCommand
- | DebuggerPausedReasonDOM
- | DebuggerPausedReasonEventListener
- | DebuggerPausedReasonException
- | DebuggerPausedReasonInstrumentation
- | DebuggerPausedReasonOOM
- | DebuggerPausedReasonOther
- | DebuggerPausedReasonPromiseRejection
- | DebuggerPausedReasonXHR
- data DebuggerBreakpointResolved = DebuggerBreakpointResolved {}
- data DebuggerDebugSymbols = DebuggerDebugSymbols {}
- data DebuggerDebugSymbolsType
- data DebuggerScriptLanguage
- data DebuggerWasmDisassemblyChunk = DebuggerWasmDisassemblyChunk {}
- data DebuggerBreakLocation = DebuggerBreakLocation {}
- data DebuggerBreakLocationType
- data DebuggerSearchMatch = DebuggerSearchMatch {}
- data DebuggerScope = DebuggerScope {}
- data DebuggerScopeType
- data DebuggerCallFrame = DebuggerCallFrame {
- debuggerCallFrameCallFrameId :: DebuggerCallFrameId
- debuggerCallFrameFunctionName :: Text
- debuggerCallFrameFunctionLocation :: Maybe DebuggerLocation
- debuggerCallFrameLocation :: DebuggerLocation
- debuggerCallFrameScopeChain :: [DebuggerScope]
- debuggerCallFrameThis :: RuntimeRemoteObject
- debuggerCallFrameReturnValue :: Maybe RuntimeRemoteObject
- debuggerCallFrameCanBeRestarted :: Maybe Bool
- data DebuggerLocationRange = DebuggerLocationRange {}
- data DebuggerScriptPosition = DebuggerScriptPosition {}
- data DebuggerLocation = DebuggerLocation {}
- type DebuggerCallFrameId = Text
- type DebuggerBreakpointId = Text
- pDebuggerContinueToLocation :: DebuggerLocation -> PDebuggerContinueToLocation
- pDebuggerDisable :: PDebuggerDisable
- pDebuggerEnable :: PDebuggerEnable
- pDebuggerEvaluateOnCallFrame :: DebuggerCallFrameId -> Text -> PDebuggerEvaluateOnCallFrame
- pDebuggerGetPossibleBreakpoints :: DebuggerLocation -> PDebuggerGetPossibleBreakpoints
- pDebuggerGetScriptSource :: RuntimeScriptId -> PDebuggerGetScriptSource
- pDebuggerDisassembleWasmModule :: RuntimeScriptId -> PDebuggerDisassembleWasmModule
- pDebuggerNextWasmDisassemblyChunk :: Text -> PDebuggerNextWasmDisassemblyChunk
- pDebuggerGetStackTrace :: RuntimeStackTraceId -> PDebuggerGetStackTrace
- pDebuggerPause :: PDebuggerPause
- pDebuggerRemoveBreakpoint :: DebuggerBreakpointId -> PDebuggerRemoveBreakpoint
- pDebuggerRestartFrame :: DebuggerCallFrameId -> PDebuggerRestartFrame
- pDebuggerResume :: PDebuggerResume
- pDebuggerSearchInContent :: RuntimeScriptId -> Text -> PDebuggerSearchInContent
- pDebuggerSetAsyncCallStackDepth :: Int -> PDebuggerSetAsyncCallStackDepth
- pDebuggerSetBlackboxPatterns :: [Text] -> PDebuggerSetBlackboxPatterns
- pDebuggerSetBlackboxedRanges :: RuntimeScriptId -> [DebuggerScriptPosition] -> PDebuggerSetBlackboxedRanges
- pDebuggerSetBreakpoint :: DebuggerLocation -> PDebuggerSetBreakpoint
- pDebuggerSetInstrumentationBreakpoint :: PDebuggerSetInstrumentationBreakpointInstrumentation -> PDebuggerSetInstrumentationBreakpoint
- pDebuggerSetBreakpointByUrl :: Int -> PDebuggerSetBreakpointByUrl
- pDebuggerSetBreakpointOnFunctionCall :: RuntimeRemoteObjectId -> PDebuggerSetBreakpointOnFunctionCall
- pDebuggerSetBreakpointsActive :: Bool -> PDebuggerSetBreakpointsActive
- pDebuggerSetPauseOnExceptions :: PDebuggerSetPauseOnExceptionsState -> PDebuggerSetPauseOnExceptions
- pDebuggerSetReturnValue :: RuntimeCallArgument -> PDebuggerSetReturnValue
- pDebuggerSetScriptSource :: RuntimeScriptId -> Text -> PDebuggerSetScriptSource
- pDebuggerSetSkipAllPauses :: Bool -> PDebuggerSetSkipAllPauses
- pDebuggerSetVariableValue :: Int -> Text -> RuntimeCallArgument -> DebuggerCallFrameId -> PDebuggerSetVariableValue
- pDebuggerStepInto :: PDebuggerStepInto
- pDebuggerStepOut :: PDebuggerStepOut
- pDebuggerStepOver :: PDebuggerStepOver
Documentation
data PDebuggerStepOver Source #
Steps over the statement.
Parameters of the stepOver
command.
PDebuggerStepOver | |
|
Instances
Eq PDebuggerStepOver Source # | |
Defined in CDP.Domains.Debugger (==) :: PDebuggerStepOver -> PDebuggerStepOver -> Bool # (/=) :: PDebuggerStepOver -> PDebuggerStepOver -> Bool # | |
Show PDebuggerStepOver Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerStepOver -> ShowS # show :: PDebuggerStepOver -> String # showList :: [PDebuggerStepOver] -> ShowS # | |
ToJSON PDebuggerStepOver Source # | |
Defined in CDP.Domains.Debugger toJSON :: PDebuggerStepOver -> Value # toEncoding :: PDebuggerStepOver -> Encoding # toJSONList :: [PDebuggerStepOver] -> Value # toEncodingList :: [PDebuggerStepOver] -> Encoding # | |
Command PDebuggerStepOver Source # | |
Defined in CDP.Domains.Debugger | |
type CommandResponse PDebuggerStepOver Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerStepOut Source #
Steps out of the function call.
Parameters of the stepOut
command.
Instances
Eq PDebuggerStepOut Source # | |
Defined in CDP.Domains.Debugger (==) :: PDebuggerStepOut -> PDebuggerStepOut -> Bool # (/=) :: PDebuggerStepOut -> PDebuggerStepOut -> Bool # | |
Show PDebuggerStepOut Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerStepOut -> ShowS # show :: PDebuggerStepOut -> String # showList :: [PDebuggerStepOut] -> ShowS # | |
ToJSON PDebuggerStepOut Source # | |
Defined in CDP.Domains.Debugger toJSON :: PDebuggerStepOut -> Value # toEncoding :: PDebuggerStepOut -> Encoding # toJSONList :: [PDebuggerStepOut] -> Value # toEncodingList :: [PDebuggerStepOut] -> Encoding # | |
Command PDebuggerStepOut Source # | |
Defined in CDP.Domains.Debugger | |
type CommandResponse PDebuggerStepOut Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerStepInto Source #
Steps into the function call.
Parameters of the stepInto
command.
PDebuggerStepInto | |
|
Instances
Eq PDebuggerStepInto Source # | |
Defined in CDP.Domains.Debugger (==) :: PDebuggerStepInto -> PDebuggerStepInto -> Bool # (/=) :: PDebuggerStepInto -> PDebuggerStepInto -> Bool # | |
Show PDebuggerStepInto Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerStepInto -> ShowS # show :: PDebuggerStepInto -> String # showList :: [PDebuggerStepInto] -> ShowS # | |
ToJSON PDebuggerStepInto Source # | |
Defined in CDP.Domains.Debugger toJSON :: PDebuggerStepInto -> Value # toEncoding :: PDebuggerStepInto -> Encoding # toJSONList :: [PDebuggerStepInto] -> Value # toEncodingList :: [PDebuggerStepInto] -> Encoding # | |
Command PDebuggerStepInto Source # | |
Defined in CDP.Domains.Debugger | |
type CommandResponse PDebuggerStepInto Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerSetVariableValue Source #
Changes value of variable in a callframe. Object-based scopes are not supported and must be mutated manually.
Parameters of the setVariableValue
command.
PDebuggerSetVariableValue | |
|
Instances
Eq PDebuggerSetVariableValue Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerSetVariableValue Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerSetVariableValue -> ShowS # show :: PDebuggerSetVariableValue -> String # showList :: [PDebuggerSetVariableValue] -> ShowS # | |
ToJSON PDebuggerSetVariableValue Source # | |
Defined in CDP.Domains.Debugger | |
Command PDebuggerSetVariableValue Source # | |
type CommandResponse PDebuggerSetVariableValue Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerSetSkipAllPauses Source #
Makes page not interrupt on any pauses (breakpoint, exception, dom exception etc).
Parameters of the setSkipAllPauses
command.
PDebuggerSetSkipAllPauses | |
|
Instances
Eq PDebuggerSetSkipAllPauses Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerSetSkipAllPauses Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerSetSkipAllPauses -> ShowS # show :: PDebuggerSetSkipAllPauses -> String # showList :: [PDebuggerSetSkipAllPauses] -> ShowS # | |
ToJSON PDebuggerSetSkipAllPauses Source # | |
Defined in CDP.Domains.Debugger | |
Command PDebuggerSetSkipAllPauses Source # | |
type CommandResponse PDebuggerSetSkipAllPauses Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerSetScriptSource Source #
DebuggerSetScriptSource | |
|
Instances
Eq DebuggerSetScriptSource Source # | |
Defined in CDP.Domains.Debugger | |
Show DebuggerSetScriptSource Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerSetScriptSource -> ShowS # show :: DebuggerSetScriptSource -> String # showList :: [DebuggerSetScriptSource] -> ShowS # | |
FromJSON DebuggerSetScriptSource Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerSetScriptSourceStatus Source #
DebuggerSetScriptSourceStatusOk | |
DebuggerSetScriptSourceStatusCompileError | |
DebuggerSetScriptSourceStatusBlockedByActiveGenerator | |
DebuggerSetScriptSourceStatusBlockedByActiveFunction |
Instances
data PDebuggerSetScriptSource Source #
Edits JavaScript source live.
In general, functions that are currently on the stack can not be edited with
a single exception: If the edited function is the top-most stack frame and
that is the only activation of that function on the stack. In this case
the live edit will be successful and a restartFrame
for the
top-most function is automatically triggered.
Parameters of the setScriptSource
command.
PDebuggerSetScriptSource | |
|
Instances
Eq PDebuggerSetScriptSource Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerSetScriptSource Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerSetScriptSource -> ShowS # show :: PDebuggerSetScriptSource -> String # showList :: [PDebuggerSetScriptSource] -> ShowS # | |
ToJSON PDebuggerSetScriptSource Source # | |
Defined in CDP.Domains.Debugger | |
Command PDebuggerSetScriptSource Source # | |
type CommandResponse PDebuggerSetScriptSource Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerSetReturnValue Source #
Changes return value in top frame. Available only at return break position.
Parameters of the setReturnValue
command.
PDebuggerSetReturnValue | |
|
Instances
Eq PDebuggerSetReturnValue Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerSetReturnValue Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerSetReturnValue -> ShowS # show :: PDebuggerSetReturnValue -> String # showList :: [PDebuggerSetReturnValue] -> ShowS # | |
ToJSON PDebuggerSetReturnValue Source # | |
Defined in CDP.Domains.Debugger | |
Command PDebuggerSetReturnValue Source # | |
type CommandResponse PDebuggerSetReturnValue Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerSetPauseOnExceptions Source #
PDebuggerSetPauseOnExceptions | |
|
Instances
data PDebuggerSetPauseOnExceptionsState Source #
Defines pause on exceptions state. Can be set to stop on all exceptions, uncaught exceptions or
no exceptions. Initial pause on exceptions state is none
.
Parameters of the setPauseOnExceptions
command.
PDebuggerSetPauseOnExceptionsStateNone | |
PDebuggerSetPauseOnExceptionsStateUncaught | |
PDebuggerSetPauseOnExceptionsStateAll |
Instances
data PDebuggerSetBreakpointsActive Source #
Activates / deactivates all breakpoints on the page.
Parameters of the setBreakpointsActive
command.
PDebuggerSetBreakpointsActive | |
|
Instances
data DebuggerSetBreakpointOnFunctionCall Source #
DebuggerSetBreakpointOnFunctionCall | |
|
Instances
data PDebuggerSetBreakpointOnFunctionCall Source #
Sets JavaScript breakpoint before each call to the given function. If another function was created from the same source as a given one, calling it will also trigger the breakpoint.
Parameters of the setBreakpointOnFunctionCall
command.
PDebuggerSetBreakpointOnFunctionCall | |
|
Instances
data DebuggerSetBreakpointByUrl Source #
DebuggerSetBreakpointByUrl | |
|
Instances
Eq DebuggerSetBreakpointByUrl Source # | |
Defined in CDP.Domains.Debugger | |
Show DebuggerSetBreakpointByUrl Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerSetBreakpointByUrl -> ShowS # show :: DebuggerSetBreakpointByUrl -> String # showList :: [DebuggerSetBreakpointByUrl] -> ShowS # | |
FromJSON DebuggerSetBreakpointByUrl Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerSetBreakpointByUrl Source #
Sets JavaScript breakpoint at given location specified either by URL or URL regex. Once this
command is issued, all existing parsed scripts will have breakpoints resolved and returned in
locations
property. Further matching script parsing will result in subsequent
breakpointResolved
events issued. This logical breakpoint will survive page reloads.
Parameters of the setBreakpointByUrl
command.
PDebuggerSetBreakpointByUrl | |
|
Instances
data DebuggerSetInstrumentationBreakpoint Source #
DebuggerSetInstrumentationBreakpoint | |
|
data PDebuggerSetInstrumentationBreakpoint Source #
Instances
data PDebuggerSetInstrumentationBreakpointInstrumentation Source #
Sets instrumentation breakpoint.
Parameters of the setInstrumentationBreakpoint
command.
PDebuggerSetInstrumentationBreakpointInstrumentationBeforeScriptExecution | |
PDebuggerSetInstrumentationBreakpointInstrumentationBeforeScriptWithSourceMapExecution |
Instances
data DebuggerSetBreakpoint Source #
DebuggerSetBreakpoint | |
|
Instances
Eq DebuggerSetBreakpoint Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerSetBreakpoint -> DebuggerSetBreakpoint -> Bool # (/=) :: DebuggerSetBreakpoint -> DebuggerSetBreakpoint -> Bool # | |
Show DebuggerSetBreakpoint Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerSetBreakpoint -> ShowS # show :: DebuggerSetBreakpoint -> String # showList :: [DebuggerSetBreakpoint] -> ShowS # | |
FromJSON DebuggerSetBreakpoint Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerSetBreakpoint # parseJSONList :: Value -> Parser [DebuggerSetBreakpoint] # |
data PDebuggerSetBreakpoint Source #
Sets JavaScript breakpoint at a given location.
Parameters of the setBreakpoint
command.
PDebuggerSetBreakpoint | |
|
Instances
Eq PDebuggerSetBreakpoint Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerSetBreakpoint Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerSetBreakpoint -> ShowS # show :: PDebuggerSetBreakpoint -> String # showList :: [PDebuggerSetBreakpoint] -> ShowS # | |
ToJSON PDebuggerSetBreakpoint Source # | |
Defined in CDP.Domains.Debugger toJSON :: PDebuggerSetBreakpoint -> Value # toEncoding :: PDebuggerSetBreakpoint -> Encoding # toJSONList :: [PDebuggerSetBreakpoint] -> Value # | |
Command PDebuggerSetBreakpoint Source # | |
type CommandResponse PDebuggerSetBreakpoint Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerSetBlackboxedRanges Source #
Makes backend skip steps in the script in blackboxed ranges. VM will try leave blacklisted scripts by performing 'step in' several times, finally resorting to 'step out' if unsuccessful. Positions array contains positions where blackbox state is changed. First interval isn't blackboxed. Array should be sorted.
Parameters of the setBlackboxedRanges
command.
Instances
Eq PDebuggerSetBlackboxedRanges Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerSetBlackboxedRanges Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerSetBlackboxedRanges -> ShowS # show :: PDebuggerSetBlackboxedRanges -> String # showList :: [PDebuggerSetBlackboxedRanges] -> ShowS # | |
ToJSON PDebuggerSetBlackboxedRanges Source # | |
Defined in CDP.Domains.Debugger | |
Command PDebuggerSetBlackboxedRanges Source # | |
type CommandResponse PDebuggerSetBlackboxedRanges Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerSetBlackboxPatterns Source #
Replace previous blackbox patterns with passed ones. Forces backend to skip stepping/pausing in scripts with url matching one of the patterns. VM will try to leave blackboxed script by performing 'step in' several times, finally resorting to 'step out' if unsuccessful.
Parameters of the setBlackboxPatterns
command.
PDebuggerSetBlackboxPatterns | |
|
Instances
Eq PDebuggerSetBlackboxPatterns Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerSetBlackboxPatterns Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerSetBlackboxPatterns -> ShowS # show :: PDebuggerSetBlackboxPatterns -> String # showList :: [PDebuggerSetBlackboxPatterns] -> ShowS # | |
ToJSON PDebuggerSetBlackboxPatterns Source # | |
Defined in CDP.Domains.Debugger | |
Command PDebuggerSetBlackboxPatterns Source # | |
type CommandResponse PDebuggerSetBlackboxPatterns Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerSetAsyncCallStackDepth Source #
Enables or disables async call stacks tracking.
Parameters of the setAsyncCallStackDepth
command.
PDebuggerSetAsyncCallStackDepth | |
|
Instances
data DebuggerSearchInContent Source #
DebuggerSearchInContent | |
|
Instances
Eq DebuggerSearchInContent Source # | |
Defined in CDP.Domains.Debugger | |
Show DebuggerSearchInContent Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerSearchInContent -> ShowS # show :: DebuggerSearchInContent -> String # showList :: [DebuggerSearchInContent] -> ShowS # | |
FromJSON DebuggerSearchInContent Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerSearchInContent Source #
Searches for given string in script content.
Parameters of the searchInContent
command.
PDebuggerSearchInContent | |
|
Instances
Eq PDebuggerSearchInContent Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerSearchInContent Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerSearchInContent -> ShowS # show :: PDebuggerSearchInContent -> String # showList :: [PDebuggerSearchInContent] -> ShowS # | |
ToJSON PDebuggerSearchInContent Source # | |
Defined in CDP.Domains.Debugger | |
Command PDebuggerSearchInContent Source # | |
type CommandResponse PDebuggerSearchInContent Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerResume Source #
Resumes JavaScript execution.
Parameters of the resume
command.
PDebuggerResume | |
|
Instances
Eq PDebuggerResume Source # | |
Defined in CDP.Domains.Debugger (==) :: PDebuggerResume -> PDebuggerResume -> Bool # (/=) :: PDebuggerResume -> PDebuggerResume -> Bool # | |
Show PDebuggerResume Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerResume -> ShowS # show :: PDebuggerResume -> String # showList :: [PDebuggerResume] -> ShowS # | |
ToJSON PDebuggerResume Source # | |
Defined in CDP.Domains.Debugger toJSON :: PDebuggerResume -> Value # toEncoding :: PDebuggerResume -> Encoding # toJSONList :: [PDebuggerResume] -> Value # toEncodingList :: [PDebuggerResume] -> Encoding # | |
Command PDebuggerResume Source # | |
Defined in CDP.Domains.Debugger commandName :: Proxy PDebuggerResume -> String Source # fromJSON :: Proxy PDebuggerResume -> Value -> Result (CommandResponse PDebuggerResume) Source # | |
type CommandResponse PDebuggerResume Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerRestartFrame Source #
PDebuggerRestartFrame | |
|
Instances
Eq PDebuggerRestartFrame Source # | |
Defined in CDP.Domains.Debugger (==) :: PDebuggerRestartFrame -> PDebuggerRestartFrame -> Bool # (/=) :: PDebuggerRestartFrame -> PDebuggerRestartFrame -> Bool # | |
Show PDebuggerRestartFrame Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerRestartFrame -> ShowS # show :: PDebuggerRestartFrame -> String # showList :: [PDebuggerRestartFrame] -> ShowS # | |
ToJSON PDebuggerRestartFrame Source # | |
Defined in CDP.Domains.Debugger toJSON :: PDebuggerRestartFrame -> Value # toEncoding :: PDebuggerRestartFrame -> Encoding # toJSONList :: [PDebuggerRestartFrame] -> Value # toEncodingList :: [PDebuggerRestartFrame] -> Encoding # | |
Command PDebuggerRestartFrame Source # | |
Defined in CDP.Domains.Debugger | |
type CommandResponse PDebuggerRestartFrame Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerRestartFrameMode Source #
Restarts particular call frame from the beginning. The old, deprecated
behavior of restartFrame
is to stay paused and allow further CDP commands
after a restart was scheduled. This can cause problems with restarting, so
we now continue execution immediatly after it has been scheduled until we
reach the beginning of the restarted frame.
To stay back-wards compatible, restartFrame
now expects a mode
parameter to be present. If the mode
parameter is missing, restartFrame
errors out.
The various return values are deprecated and callFrames
is always empty.
Use the call frames from the `Debugger#paused` events instead, that fires
once V8 pauses at the beginning of the restarted function.
Parameters of the restartFrame
command.
Instances
data PDebuggerRemoveBreakpoint Source #
Removes JavaScript breakpoint.
Parameters of the removeBreakpoint
command.
Instances
Eq PDebuggerRemoveBreakpoint Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerRemoveBreakpoint Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerRemoveBreakpoint -> ShowS # show :: PDebuggerRemoveBreakpoint -> String # showList :: [PDebuggerRemoveBreakpoint] -> ShowS # | |
ToJSON PDebuggerRemoveBreakpoint Source # | |
Defined in CDP.Domains.Debugger | |
Command PDebuggerRemoveBreakpoint Source # | |
type CommandResponse PDebuggerRemoveBreakpoint Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerPause Source #
Stops on the next JavaScript statement.
Parameters of the pause
command.
Instances
Eq PDebuggerPause Source # | |
Defined in CDP.Domains.Debugger (==) :: PDebuggerPause -> PDebuggerPause -> Bool # (/=) :: PDebuggerPause -> PDebuggerPause -> Bool # | |
Show PDebuggerPause Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerPause -> ShowS # show :: PDebuggerPause -> String # showList :: [PDebuggerPause] -> ShowS # | |
ToJSON PDebuggerPause Source # | |
Defined in CDP.Domains.Debugger toJSON :: PDebuggerPause -> Value # toEncoding :: PDebuggerPause -> Encoding # toJSONList :: [PDebuggerPause] -> Value # toEncodingList :: [PDebuggerPause] -> Encoding # | |
Command PDebuggerPause Source # | |
Defined in CDP.Domains.Debugger commandName :: Proxy PDebuggerPause -> String Source # fromJSON :: Proxy PDebuggerPause -> Value -> Result (CommandResponse PDebuggerPause) Source # | |
type CommandResponse PDebuggerPause Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerGetStackTrace Source #
Instances
Eq DebuggerGetStackTrace Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerGetStackTrace -> DebuggerGetStackTrace -> Bool # (/=) :: DebuggerGetStackTrace -> DebuggerGetStackTrace -> Bool # | |
Show DebuggerGetStackTrace Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerGetStackTrace -> ShowS # show :: DebuggerGetStackTrace -> String # showList :: [DebuggerGetStackTrace] -> ShowS # | |
FromJSON DebuggerGetStackTrace Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerGetStackTrace # parseJSONList :: Value -> Parser [DebuggerGetStackTrace] # |
data PDebuggerGetStackTrace Source #
Returns stack trace with given stackTraceId
.
Parameters of the getStackTrace
command.
Instances
Eq PDebuggerGetStackTrace Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerGetStackTrace Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerGetStackTrace -> ShowS # show :: PDebuggerGetStackTrace -> String # showList :: [PDebuggerGetStackTrace] -> ShowS # | |
ToJSON PDebuggerGetStackTrace Source # | |
Defined in CDP.Domains.Debugger toJSON :: PDebuggerGetStackTrace -> Value # toEncoding :: PDebuggerGetStackTrace -> Encoding # toJSONList :: [PDebuggerGetStackTrace] -> Value # | |
Command PDebuggerGetStackTrace Source # | |
type CommandResponse PDebuggerGetStackTrace Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerNextWasmDisassemblyChunk Source #
DebuggerNextWasmDisassemblyChunk | |
|
Instances
data PDebuggerNextWasmDisassemblyChunk Source #
Disassemble the next chunk of lines for the module corresponding to the stream. If disassembly is complete, this API will invalidate the streamId and return an empty chunk. Any subsequent calls for the now invalid stream will return errors.
Parameters of the nextWasmDisassemblyChunk
command.
Instances
data DebuggerDisassembleWasmModule Source #
DebuggerDisassembleWasmModule | |
|
Instances
data PDebuggerDisassembleWasmModule Source #
Parameters of the disassembleWasmModule
command.
PDebuggerDisassembleWasmModule | |
|
data DebuggerGetScriptSource Source #
DebuggerGetScriptSource | |
|
Instances
Eq DebuggerGetScriptSource Source # | |
Defined in CDP.Domains.Debugger | |
Show DebuggerGetScriptSource Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerGetScriptSource -> ShowS # show :: DebuggerGetScriptSource -> String # showList :: [DebuggerGetScriptSource] -> ShowS # | |
FromJSON DebuggerGetScriptSource Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerGetScriptSource Source #
Returns source for the script with given id.
Parameters of the getScriptSource
command.
PDebuggerGetScriptSource | |
|
Instances
Eq PDebuggerGetScriptSource Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerGetScriptSource Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerGetScriptSource -> ShowS # show :: PDebuggerGetScriptSource -> String # showList :: [PDebuggerGetScriptSource] -> ShowS # | |
ToJSON PDebuggerGetScriptSource Source # | |
Defined in CDP.Domains.Debugger | |
Command PDebuggerGetScriptSource Source # | |
type CommandResponse PDebuggerGetScriptSource Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerGetPossibleBreakpoints Source #
DebuggerGetPossibleBreakpoints | |
|
Instances
data PDebuggerGetPossibleBreakpoints Source #
Returns possible locations for breakpoint. scriptId in start and end range locations should be the same.
Parameters of the getPossibleBreakpoints
command.
PDebuggerGetPossibleBreakpoints | |
|
data DebuggerEvaluateOnCallFrame Source #
DebuggerEvaluateOnCallFrame | |
|
Instances
Eq DebuggerEvaluateOnCallFrame Source # | |
Defined in CDP.Domains.Debugger | |
Show DebuggerEvaluateOnCallFrame Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerEvaluateOnCallFrame -> ShowS # show :: DebuggerEvaluateOnCallFrame -> String # showList :: [DebuggerEvaluateOnCallFrame] -> ShowS # | |
FromJSON DebuggerEvaluateOnCallFrame Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerEvaluateOnCallFrame Source #
Evaluates expression on a given call frame.
Parameters of the evaluateOnCallFrame
command.
PDebuggerEvaluateOnCallFrame | |
|
Instances
data DebuggerEnable Source #
DebuggerEnable | |
|
Instances
Eq DebuggerEnable Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerEnable -> DebuggerEnable -> Bool # (/=) :: DebuggerEnable -> DebuggerEnable -> Bool # | |
Show DebuggerEnable Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerEnable -> ShowS # show :: DebuggerEnable -> String # showList :: [DebuggerEnable] -> ShowS # | |
FromJSON DebuggerEnable Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerEnable # parseJSONList :: Value -> Parser [DebuggerEnable] # |
data PDebuggerEnable Source #
Enables debugger for the given page. Clients should not assume that the debugging has been enabled until the result for this command is received.
Parameters of the enable
command.
PDebuggerEnable | |
|
Instances
Eq PDebuggerEnable Source # | |
Defined in CDP.Domains.Debugger (==) :: PDebuggerEnable -> PDebuggerEnable -> Bool # (/=) :: PDebuggerEnable -> PDebuggerEnable -> Bool # | |
Show PDebuggerEnable Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerEnable -> ShowS # show :: PDebuggerEnable -> String # showList :: [PDebuggerEnable] -> ShowS # | |
ToJSON PDebuggerEnable Source # | |
Defined in CDP.Domains.Debugger toJSON :: PDebuggerEnable -> Value # toEncoding :: PDebuggerEnable -> Encoding # toJSONList :: [PDebuggerEnable] -> Value # toEncodingList :: [PDebuggerEnable] -> Encoding # | |
Command PDebuggerEnable Source # | |
Defined in CDP.Domains.Debugger commandName :: Proxy PDebuggerEnable -> String Source # fromJSON :: Proxy PDebuggerEnable -> Value -> Result (CommandResponse PDebuggerEnable) Source # | |
type CommandResponse PDebuggerEnable Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerDisable Source #
Disables debugger for given page.
Parameters of the disable
command.
Instances
Eq PDebuggerDisable Source # | |
Defined in CDP.Domains.Debugger (==) :: PDebuggerDisable -> PDebuggerDisable -> Bool # (/=) :: PDebuggerDisable -> PDebuggerDisable -> Bool # | |
Show PDebuggerDisable Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerDisable -> ShowS # show :: PDebuggerDisable -> String # showList :: [PDebuggerDisable] -> ShowS # | |
ToJSON PDebuggerDisable Source # | |
Defined in CDP.Domains.Debugger toJSON :: PDebuggerDisable -> Value # toEncoding :: PDebuggerDisable -> Encoding # toJSONList :: [PDebuggerDisable] -> Value # toEncodingList :: [PDebuggerDisable] -> Encoding # | |
Command PDebuggerDisable Source # | |
Defined in CDP.Domains.Debugger | |
type CommandResponse PDebuggerDisable Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerContinueToLocation Source #
Instances
Eq PDebuggerContinueToLocation Source # | |
Defined in CDP.Domains.Debugger | |
Show PDebuggerContinueToLocation Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> PDebuggerContinueToLocation -> ShowS # show :: PDebuggerContinueToLocation -> String # showList :: [PDebuggerContinueToLocation] -> ShowS # | |
ToJSON PDebuggerContinueToLocation Source # | |
Defined in CDP.Domains.Debugger | |
Command PDebuggerContinueToLocation Source # | |
type CommandResponse PDebuggerContinueToLocation Source # | |
Defined in CDP.Domains.Debugger |
data PDebuggerContinueToLocationTargetCallFrames Source #
Continues execution until specific location is reached.
Parameters of the continueToLocation
command.
Instances
data DebuggerScriptParsed Source #
Type of the scriptParsed
event.
DebuggerScriptParsed | |
|
Instances
Eq DebuggerScriptParsed Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerScriptParsed -> DebuggerScriptParsed -> Bool # (/=) :: DebuggerScriptParsed -> DebuggerScriptParsed -> Bool # | |
Show DebuggerScriptParsed Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerScriptParsed -> ShowS # show :: DebuggerScriptParsed -> String # showList :: [DebuggerScriptParsed] -> ShowS # | |
FromJSON DebuggerScriptParsed Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerScriptParsed # parseJSONList :: Value -> Parser [DebuggerScriptParsed] # | |
Event DebuggerScriptParsed Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerScriptFailedToParse Source #
Type of the scriptFailedToParse
event.
DebuggerScriptFailedToParse | |
|
Instances
Eq DebuggerScriptFailedToParse Source # | |
Defined in CDP.Domains.Debugger | |
Show DebuggerScriptFailedToParse Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerScriptFailedToParse -> ShowS # show :: DebuggerScriptFailedToParse -> String # showList :: [DebuggerScriptFailedToParse] -> ShowS # | |
FromJSON DebuggerScriptFailedToParse Source # | |
Defined in CDP.Domains.Debugger | |
Event DebuggerScriptFailedToParse Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerResumed Source #
Type of the resumed
event.
Instances
Eq DebuggerResumed Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerResumed -> DebuggerResumed -> Bool # (/=) :: DebuggerResumed -> DebuggerResumed -> Bool # | |
Read DebuggerResumed Source # | |
Defined in CDP.Domains.Debugger | |
Show DebuggerResumed Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerResumed -> ShowS # show :: DebuggerResumed -> String # showList :: [DebuggerResumed] -> ShowS # | |
FromJSON DebuggerResumed Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerResumed # parseJSONList :: Value -> Parser [DebuggerResumed] # | |
Event DebuggerResumed Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerPaused Source #
DebuggerPaused | |
|
Instances
Eq DebuggerPaused Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerPaused -> DebuggerPaused -> Bool # (/=) :: DebuggerPaused -> DebuggerPaused -> Bool # | |
Show DebuggerPaused Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerPaused -> ShowS # show :: DebuggerPaused -> String # showList :: [DebuggerPaused] -> ShowS # | |
FromJSON DebuggerPaused Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerPaused # parseJSONList :: Value -> Parser [DebuggerPaused] # | |
Event DebuggerPaused Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerPausedReason Source #
Type of the paused
event.
Instances
data DebuggerBreakpointResolved Source #
Type of the breakpointResolved
event.
DebuggerBreakpointResolved | |
|
Instances
Eq DebuggerBreakpointResolved Source # | |
Defined in CDP.Domains.Debugger | |
Show DebuggerBreakpointResolved Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerBreakpointResolved -> ShowS # show :: DebuggerBreakpointResolved -> String # showList :: [DebuggerBreakpointResolved] -> ShowS # | |
FromJSON DebuggerBreakpointResolved Source # | |
Defined in CDP.Domains.Debugger | |
Event DebuggerBreakpointResolved Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerDebugSymbols Source #
DebuggerDebugSymbols | |
|
Instances
Eq DebuggerDebugSymbols Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerDebugSymbols -> DebuggerDebugSymbols -> Bool # (/=) :: DebuggerDebugSymbols -> DebuggerDebugSymbols -> Bool # | |
Show DebuggerDebugSymbols Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerDebugSymbols -> ShowS # show :: DebuggerDebugSymbols -> String # showList :: [DebuggerDebugSymbols] -> ShowS # | |
ToJSON DebuggerDebugSymbols Source # | |
Defined in CDP.Domains.Debugger toJSON :: DebuggerDebugSymbols -> Value # toEncoding :: DebuggerDebugSymbols -> Encoding # toJSONList :: [DebuggerDebugSymbols] -> Value # toEncodingList :: [DebuggerDebugSymbols] -> Encoding # | |
FromJSON DebuggerDebugSymbols Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerDebugSymbols # parseJSONList :: Value -> Parser [DebuggerDebugSymbols] # |
data DebuggerDebugSymbolsType Source #
Type DebugSymbols
.
Debug symbols available for a wasm script.
DebuggerDebugSymbolsTypeNone | |
DebuggerDebugSymbolsTypeSourceMap | |
DebuggerDebugSymbolsTypeEmbeddedDWARF | |
DebuggerDebugSymbolsTypeExternalDWARF |
Instances
data DebuggerScriptLanguage Source #
Type ScriptLanguage
.
Enum of possible script languages.
Instances
data DebuggerWasmDisassemblyChunk Source #
Type WasmDisassemblyChunk
.
DebuggerWasmDisassemblyChunk | |
|
Instances
Eq DebuggerWasmDisassemblyChunk Source # | |
Defined in CDP.Domains.Debugger | |
Show DebuggerWasmDisassemblyChunk Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerWasmDisassemblyChunk -> ShowS # show :: DebuggerWasmDisassemblyChunk -> String # showList :: [DebuggerWasmDisassemblyChunk] -> ShowS # | |
ToJSON DebuggerWasmDisassemblyChunk Source # | |
Defined in CDP.Domains.Debugger | |
FromJSON DebuggerWasmDisassemblyChunk Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerBreakLocation Source #
DebuggerBreakLocation | |
|
Instances
Eq DebuggerBreakLocation Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerBreakLocation -> DebuggerBreakLocation -> Bool # (/=) :: DebuggerBreakLocation -> DebuggerBreakLocation -> Bool # | |
Show DebuggerBreakLocation Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerBreakLocation -> ShowS # show :: DebuggerBreakLocation -> String # showList :: [DebuggerBreakLocation] -> ShowS # | |
ToJSON DebuggerBreakLocation Source # | |
Defined in CDP.Domains.Debugger toJSON :: DebuggerBreakLocation -> Value # toEncoding :: DebuggerBreakLocation -> Encoding # toJSONList :: [DebuggerBreakLocation] -> Value # toEncodingList :: [DebuggerBreakLocation] -> Encoding # | |
FromJSON DebuggerBreakLocation Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerBreakLocation # parseJSONList :: Value -> Parser [DebuggerBreakLocation] # |
data DebuggerBreakLocationType Source #
Type BreakLocation
.
DebuggerBreakLocationTypeDebuggerStatement | |
DebuggerBreakLocationTypeCall | |
DebuggerBreakLocationTypeReturn |
Instances
data DebuggerSearchMatch Source #
Type SearchMatch
.
Search match for resource.
DebuggerSearchMatch | |
|
Instances
Eq DebuggerSearchMatch Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerSearchMatch -> DebuggerSearchMatch -> Bool # (/=) :: DebuggerSearchMatch -> DebuggerSearchMatch -> Bool # | |
Show DebuggerSearchMatch Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerSearchMatch -> ShowS # show :: DebuggerSearchMatch -> String # showList :: [DebuggerSearchMatch] -> ShowS # | |
ToJSON DebuggerSearchMatch Source # | |
Defined in CDP.Domains.Debugger toJSON :: DebuggerSearchMatch -> Value # toEncoding :: DebuggerSearchMatch -> Encoding # toJSONList :: [DebuggerSearchMatch] -> Value # toEncodingList :: [DebuggerSearchMatch] -> Encoding # | |
FromJSON DebuggerSearchMatch Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerSearchMatch # parseJSONList :: Value -> Parser [DebuggerSearchMatch] # |
data DebuggerScope Source #
DebuggerScope | |
|
Instances
Eq DebuggerScope Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerScope -> DebuggerScope -> Bool # (/=) :: DebuggerScope -> DebuggerScope -> Bool # | |
Show DebuggerScope Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerScope -> ShowS # show :: DebuggerScope -> String # showList :: [DebuggerScope] -> ShowS # | |
ToJSON DebuggerScope Source # | |
Defined in CDP.Domains.Debugger toJSON :: DebuggerScope -> Value # toEncoding :: DebuggerScope -> Encoding # toJSONList :: [DebuggerScope] -> Value # toEncodingList :: [DebuggerScope] -> Encoding # | |
FromJSON DebuggerScope Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerScope # parseJSONList :: Value -> Parser [DebuggerScope] # |
data DebuggerScopeType Source #
Type Scope
.
Scope description.
Instances
data DebuggerCallFrame Source #
Type CallFrame
.
JavaScript call frame. Array of call frames form the call stack.
DebuggerCallFrame | |
|
Instances
Eq DebuggerCallFrame Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerCallFrame -> DebuggerCallFrame -> Bool # (/=) :: DebuggerCallFrame -> DebuggerCallFrame -> Bool # | |
Show DebuggerCallFrame Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerCallFrame -> ShowS # show :: DebuggerCallFrame -> String # showList :: [DebuggerCallFrame] -> ShowS # | |
ToJSON DebuggerCallFrame Source # | |
Defined in CDP.Domains.Debugger toJSON :: DebuggerCallFrame -> Value # toEncoding :: DebuggerCallFrame -> Encoding # toJSONList :: [DebuggerCallFrame] -> Value # toEncodingList :: [DebuggerCallFrame] -> Encoding # | |
FromJSON DebuggerCallFrame Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerCallFrame # parseJSONList :: Value -> Parser [DebuggerCallFrame] # |
data DebuggerLocationRange Source #
Type LocationRange
.
Location range within one script.
Instances
Eq DebuggerLocationRange Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerLocationRange -> DebuggerLocationRange -> Bool # (/=) :: DebuggerLocationRange -> DebuggerLocationRange -> Bool # | |
Show DebuggerLocationRange Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerLocationRange -> ShowS # show :: DebuggerLocationRange -> String # showList :: [DebuggerLocationRange] -> ShowS # | |
ToJSON DebuggerLocationRange Source # | |
Defined in CDP.Domains.Debugger toJSON :: DebuggerLocationRange -> Value # toEncoding :: DebuggerLocationRange -> Encoding # toJSONList :: [DebuggerLocationRange] -> Value # toEncodingList :: [DebuggerLocationRange] -> Encoding # | |
FromJSON DebuggerLocationRange Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerLocationRange # parseJSONList :: Value -> Parser [DebuggerLocationRange] # |
data DebuggerScriptPosition Source #
Type ScriptPosition
.
Location in the source code.
Instances
Eq DebuggerScriptPosition Source # | |
Defined in CDP.Domains.Debugger | |
Show DebuggerScriptPosition Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerScriptPosition -> ShowS # show :: DebuggerScriptPosition -> String # showList :: [DebuggerScriptPosition] -> ShowS # | |
ToJSON DebuggerScriptPosition Source # | |
Defined in CDP.Domains.Debugger toJSON :: DebuggerScriptPosition -> Value # toEncoding :: DebuggerScriptPosition -> Encoding # toJSONList :: [DebuggerScriptPosition] -> Value # | |
FromJSON DebuggerScriptPosition Source # | |
Defined in CDP.Domains.Debugger |
data DebuggerLocation Source #
Type Location
.
Location in the source code.
DebuggerLocation | |
|
Instances
Eq DebuggerLocation Source # | |
Defined in CDP.Domains.Debugger (==) :: DebuggerLocation -> DebuggerLocation -> Bool # (/=) :: DebuggerLocation -> DebuggerLocation -> Bool # | |
Show DebuggerLocation Source # | |
Defined in CDP.Domains.Debugger showsPrec :: Int -> DebuggerLocation -> ShowS # show :: DebuggerLocation -> String # showList :: [DebuggerLocation] -> ShowS # | |
ToJSON DebuggerLocation Source # | |
Defined in CDP.Domains.Debugger toJSON :: DebuggerLocation -> Value # toEncoding :: DebuggerLocation -> Encoding # toJSONList :: [DebuggerLocation] -> Value # toEncodingList :: [DebuggerLocation] -> Encoding # | |
FromJSON DebuggerLocation Source # | |
Defined in CDP.Domains.Debugger parseJSON :: Value -> Parser DebuggerLocation # parseJSONList :: Value -> Parser [DebuggerLocation] # |
type DebuggerCallFrameId = Text Source #
Type CallFrameId
.
Call frame identifier.
type DebuggerBreakpointId = Text Source #
Type BreakpointId
.
Breakpoint identifier.
pDebuggerEvaluateOnCallFrame :: DebuggerCallFrameId -> Text -> PDebuggerEvaluateOnCallFrame Source #
pDebuggerSetBlackboxedRanges :: RuntimeScriptId -> [DebuggerScriptPosition] -> PDebuggerSetBlackboxedRanges Source #
pDebuggerSetInstrumentationBreakpoint :: PDebuggerSetInstrumentationBreakpointInstrumentation -> PDebuggerSetInstrumentationBreakpoint Source #
pDebuggerSetBreakpointOnFunctionCall :: RuntimeRemoteObjectId -> PDebuggerSetBreakpointOnFunctionCall Source #
pDebuggerSetPauseOnExceptions :: PDebuggerSetPauseOnExceptionsState -> PDebuggerSetPauseOnExceptions Source #