Safe Haskell | None |
---|---|
Language | Haskell2010 |
CDP.Domains.Runtime
Description
Runtime
Runtime domain exposes JavaScript runtime by means of remote evaluation and mirror objects. Evaluation results are returned as mirror object that expose object type, string representation and unique identifier that can be used for further object reference. Original objects are maintained in memory unless they are either explicitly released or are released along with the other objects in their object group.
Synopsis
- data RuntimeGetExceptionDetails = RuntimeGetExceptionDetails {}
- data PRuntimeGetExceptionDetails = PRuntimeGetExceptionDetails {}
- data PRuntimeRemoveBinding = PRuntimeRemoveBinding {}
- data PRuntimeAddBinding = PRuntimeAddBinding {}
- data PRuntimeTerminateExecution = PRuntimeTerminateExecution
- data PRuntimeSetMaxCallStackSizeToCapture = PRuntimeSetMaxCallStackSizeToCapture {}
- data PRuntimeSetCustomObjectFormatterEnabled = PRuntimeSetCustomObjectFormatterEnabled {}
- data PRuntimeSetAsyncCallStackDepth = PRuntimeSetAsyncCallStackDepth {}
- data RuntimeRunScript = RuntimeRunScript {}
- data PRuntimeRunScript = PRuntimeRunScript {
- pRuntimeRunScriptScriptId :: RuntimeScriptId
- pRuntimeRunScriptExecutionContextId :: Maybe RuntimeExecutionContextId
- pRuntimeRunScriptObjectGroup :: Maybe Text
- pRuntimeRunScriptSilent :: Maybe Bool
- pRuntimeRunScriptIncludeCommandLineAPI :: Maybe Bool
- pRuntimeRunScriptReturnByValue :: Maybe Bool
- pRuntimeRunScriptGeneratePreview :: Maybe Bool
- pRuntimeRunScriptAwaitPromise :: Maybe Bool
- data PRuntimeRunIfWaitingForDebugger = PRuntimeRunIfWaitingForDebugger
- data PRuntimeReleaseObjectGroup = PRuntimeReleaseObjectGroup {}
- data PRuntimeReleaseObject = PRuntimeReleaseObject {}
- data RuntimeQueryObjects = RuntimeQueryObjects {}
- data PRuntimeQueryObjects = PRuntimeQueryObjects {}
- data RuntimeGlobalLexicalScopeNames = RuntimeGlobalLexicalScopeNames {}
- data PRuntimeGlobalLexicalScopeNames = PRuntimeGlobalLexicalScopeNames {}
- data RuntimeGetProperties = RuntimeGetProperties {}
- data PRuntimeGetProperties = PRuntimeGetProperties {}
- data RuntimeGetHeapUsage = RuntimeGetHeapUsage {}
- data PRuntimeGetHeapUsage = PRuntimeGetHeapUsage
- data RuntimeGetIsolateId = RuntimeGetIsolateId {}
- data PRuntimeGetIsolateId = PRuntimeGetIsolateId
- data RuntimeEvaluate = RuntimeEvaluate {}
- data PRuntimeEvaluate = PRuntimeEvaluate {
- pRuntimeEvaluateExpression :: Text
- pRuntimeEvaluateObjectGroup :: Maybe Text
- pRuntimeEvaluateIncludeCommandLineAPI :: Maybe Bool
- pRuntimeEvaluateSilent :: Maybe Bool
- pRuntimeEvaluateContextId :: Maybe RuntimeExecutionContextId
- pRuntimeEvaluateReturnByValue :: Maybe Bool
- pRuntimeEvaluateGeneratePreview :: Maybe Bool
- pRuntimeEvaluateUserGesture :: Maybe Bool
- pRuntimeEvaluateAwaitPromise :: Maybe Bool
- pRuntimeEvaluateThrowOnSideEffect :: Maybe Bool
- pRuntimeEvaluateTimeout :: Maybe RuntimeTimeDelta
- pRuntimeEvaluateDisableBreaks :: Maybe Bool
- pRuntimeEvaluateReplMode :: Maybe Bool
- pRuntimeEvaluateAllowUnsafeEvalBlockedByCSP :: Maybe Bool
- pRuntimeEvaluateUniqueContextId :: Maybe Text
- pRuntimeEvaluateGenerateWebDriverValue :: Maybe Bool
- data PRuntimeEnable = PRuntimeEnable
- data PRuntimeDiscardConsoleEntries = PRuntimeDiscardConsoleEntries
- data PRuntimeDisable = PRuntimeDisable
- data RuntimeCompileScript = RuntimeCompileScript {}
- data PRuntimeCompileScript = PRuntimeCompileScript {}
- data RuntimeCallFunctionOn = RuntimeCallFunctionOn {}
- data PRuntimeCallFunctionOn = PRuntimeCallFunctionOn {
- pRuntimeCallFunctionOnFunctionDeclaration :: Text
- pRuntimeCallFunctionOnObjectId :: Maybe RuntimeRemoteObjectId
- pRuntimeCallFunctionOnArguments :: Maybe [RuntimeCallArgument]
- pRuntimeCallFunctionOnSilent :: Maybe Bool
- pRuntimeCallFunctionOnReturnByValue :: Maybe Bool
- pRuntimeCallFunctionOnGeneratePreview :: Maybe Bool
- pRuntimeCallFunctionOnUserGesture :: Maybe Bool
- pRuntimeCallFunctionOnAwaitPromise :: Maybe Bool
- pRuntimeCallFunctionOnExecutionContextId :: Maybe RuntimeExecutionContextId
- pRuntimeCallFunctionOnObjectGroup :: Maybe Text
- pRuntimeCallFunctionOnThrowOnSideEffect :: Maybe Bool
- pRuntimeCallFunctionOnGenerateWebDriverValue :: Maybe Bool
- data RuntimeAwaitPromise = RuntimeAwaitPromise {}
- data PRuntimeAwaitPromise = PRuntimeAwaitPromise {}
- data RuntimeInspectRequested = RuntimeInspectRequested {}
- data RuntimeExecutionContextsCleared = RuntimeExecutionContextsCleared
- data RuntimeExecutionContextDestroyed = RuntimeExecutionContextDestroyed {}
- data RuntimeExecutionContextCreated = RuntimeExecutionContextCreated {}
- data RuntimeExceptionThrown = RuntimeExceptionThrown {}
- data RuntimeExceptionRevoked = RuntimeExceptionRevoked {}
- data RuntimeConsoleAPICalled = RuntimeConsoleAPICalled {
- runtimeConsoleAPICalledType :: RuntimeConsoleAPICalledType
- runtimeConsoleAPICalledArgs :: [RuntimeRemoteObject]
- runtimeConsoleAPICalledExecutionContextId :: RuntimeExecutionContextId
- runtimeConsoleAPICalledTimestamp :: RuntimeTimestamp
- runtimeConsoleAPICalledStackTrace :: Maybe RuntimeStackTrace
- runtimeConsoleAPICalledContext :: Maybe Text
- data RuntimeConsoleAPICalledType
- = RuntimeConsoleAPICalledTypeLog
- | RuntimeConsoleAPICalledTypeDebug
- | RuntimeConsoleAPICalledTypeInfo
- | RuntimeConsoleAPICalledTypeError
- | RuntimeConsoleAPICalledTypeWarning
- | RuntimeConsoleAPICalledTypeDir
- | RuntimeConsoleAPICalledTypeDirxml
- | RuntimeConsoleAPICalledTypeTable
- | RuntimeConsoleAPICalledTypeTrace
- | RuntimeConsoleAPICalledTypeClear
- | RuntimeConsoleAPICalledTypeStartGroup
- | RuntimeConsoleAPICalledTypeStartGroupCollapsed
- | RuntimeConsoleAPICalledTypeEndGroup
- | RuntimeConsoleAPICalledTypeAssert
- | RuntimeConsoleAPICalledTypeProfile
- | RuntimeConsoleAPICalledTypeProfileEnd
- | RuntimeConsoleAPICalledTypeCount
- | RuntimeConsoleAPICalledTypeTimeEnd
- data RuntimeBindingCalled = RuntimeBindingCalled {}
- data RuntimeStackTraceId = RuntimeStackTraceId {}
- type RuntimeUniqueDebuggerId = Text
- data RuntimeStackTrace = RuntimeStackTrace {}
- data RuntimeCallFrame = RuntimeCallFrame {}
- type RuntimeTimeDelta = Double
- type RuntimeTimestamp = Double
- data RuntimeExceptionDetails = RuntimeExceptionDetails {
- runtimeExceptionDetailsExceptionId :: Int
- runtimeExceptionDetailsText :: Text
- runtimeExceptionDetailsLineNumber :: Int
- runtimeExceptionDetailsColumnNumber :: Int
- runtimeExceptionDetailsScriptId :: Maybe RuntimeScriptId
- runtimeExceptionDetailsUrl :: Maybe Text
- runtimeExceptionDetailsStackTrace :: Maybe RuntimeStackTrace
- runtimeExceptionDetailsException :: Maybe RuntimeRemoteObject
- runtimeExceptionDetailsExecutionContextId :: Maybe RuntimeExecutionContextId
- runtimeExceptionDetailsExceptionMetaData :: Maybe [(Text, Text)]
- data RuntimeExecutionContextDescription = RuntimeExecutionContextDescription {}
- type RuntimeExecutionContextId = Int
- data RuntimeCallArgument = RuntimeCallArgument {}
- data RuntimePrivatePropertyDescriptor = RuntimePrivatePropertyDescriptor {}
- data RuntimeInternalPropertyDescriptor = RuntimeInternalPropertyDescriptor {}
- data RuntimePropertyDescriptor = RuntimePropertyDescriptor {
- runtimePropertyDescriptorName :: Text
- runtimePropertyDescriptorValue :: Maybe RuntimeRemoteObject
- runtimePropertyDescriptorWritable :: Maybe Bool
- runtimePropertyDescriptorGet :: Maybe RuntimeRemoteObject
- runtimePropertyDescriptorSet :: Maybe RuntimeRemoteObject
- runtimePropertyDescriptorConfigurable :: Bool
- runtimePropertyDescriptorEnumerable :: Bool
- runtimePropertyDescriptorWasThrown :: Maybe Bool
- runtimePropertyDescriptorIsOwn :: Maybe Bool
- runtimePropertyDescriptorSymbol :: Maybe RuntimeRemoteObject
- data RuntimeEntryPreview = RuntimeEntryPreview {}
- data RuntimePropertyPreview = RuntimePropertyPreview {}
- data RuntimePropertyPreviewSubtype
- = RuntimePropertyPreviewSubtypeArray
- | RuntimePropertyPreviewSubtypeNull
- | RuntimePropertyPreviewSubtypeNode
- | RuntimePropertyPreviewSubtypeRegexp
- | RuntimePropertyPreviewSubtypeDate
- | RuntimePropertyPreviewSubtypeMap
- | RuntimePropertyPreviewSubtypeSet
- | RuntimePropertyPreviewSubtypeWeakmap
- | RuntimePropertyPreviewSubtypeWeakset
- | RuntimePropertyPreviewSubtypeIterator
- | RuntimePropertyPreviewSubtypeGenerator
- | RuntimePropertyPreviewSubtypeError
- | RuntimePropertyPreviewSubtypeProxy
- | RuntimePropertyPreviewSubtypePromise
- | RuntimePropertyPreviewSubtypeTypedarray
- | RuntimePropertyPreviewSubtypeArraybuffer
- | RuntimePropertyPreviewSubtypeDataview
- | RuntimePropertyPreviewSubtypeWebassemblymemory
- | RuntimePropertyPreviewSubtypeWasmvalue
- data RuntimePropertyPreviewType
- = RuntimePropertyPreviewTypeObject
- | RuntimePropertyPreviewTypeFunction
- | RuntimePropertyPreviewTypeUndefined
- | RuntimePropertyPreviewTypeString
- | RuntimePropertyPreviewTypeNumber
- | RuntimePropertyPreviewTypeBoolean
- | RuntimePropertyPreviewTypeSymbol
- | RuntimePropertyPreviewTypeAccessor
- | RuntimePropertyPreviewTypeBigint
- data RuntimeObjectPreview = RuntimeObjectPreview {
- runtimeObjectPreviewType :: RuntimeObjectPreviewType
- runtimeObjectPreviewSubtype :: Maybe RuntimeObjectPreviewSubtype
- runtimeObjectPreviewDescription :: Maybe Text
- runtimeObjectPreviewOverflow :: Bool
- runtimeObjectPreviewProperties :: [RuntimePropertyPreview]
- runtimeObjectPreviewEntries :: Maybe [RuntimeEntryPreview]
- data RuntimeObjectPreviewSubtype
- = RuntimeObjectPreviewSubtypeArray
- | RuntimeObjectPreviewSubtypeNull
- | RuntimeObjectPreviewSubtypeNode
- | RuntimeObjectPreviewSubtypeRegexp
- | RuntimeObjectPreviewSubtypeDate
- | RuntimeObjectPreviewSubtypeMap
- | RuntimeObjectPreviewSubtypeSet
- | RuntimeObjectPreviewSubtypeWeakmap
- | RuntimeObjectPreviewSubtypeWeakset
- | RuntimeObjectPreviewSubtypeIterator
- | RuntimeObjectPreviewSubtypeGenerator
- | RuntimeObjectPreviewSubtypeError
- | RuntimeObjectPreviewSubtypeProxy
- | RuntimeObjectPreviewSubtypePromise
- | RuntimeObjectPreviewSubtypeTypedarray
- | RuntimeObjectPreviewSubtypeArraybuffer
- | RuntimeObjectPreviewSubtypeDataview
- | RuntimeObjectPreviewSubtypeWebassemblymemory
- | RuntimeObjectPreviewSubtypeWasmvalue
- data RuntimeObjectPreviewType
- data RuntimeCustomPreview = RuntimeCustomPreview {}
- data RuntimeRemoteObject = RuntimeRemoteObject {
- runtimeRemoteObjectType :: RuntimeRemoteObjectType
- runtimeRemoteObjectSubtype :: Maybe RuntimeRemoteObjectSubtype
- runtimeRemoteObjectClassName :: Maybe Text
- runtimeRemoteObjectValue :: Maybe Value
- runtimeRemoteObjectUnserializableValue :: Maybe RuntimeUnserializableValue
- runtimeRemoteObjectDescription :: Maybe Text
- runtimeRemoteObjectWebDriverValue :: Maybe RuntimeWebDriverValue
- runtimeRemoteObjectObjectId :: Maybe RuntimeRemoteObjectId
- runtimeRemoteObjectPreview :: Maybe RuntimeObjectPreview
- runtimeRemoteObjectCustomPreview :: Maybe RuntimeCustomPreview
- data RuntimeRemoteObjectSubtype
- = RuntimeRemoteObjectSubtypeArray
- | RuntimeRemoteObjectSubtypeNull
- | RuntimeRemoteObjectSubtypeNode
- | RuntimeRemoteObjectSubtypeRegexp
- | RuntimeRemoteObjectSubtypeDate
- | RuntimeRemoteObjectSubtypeMap
- | RuntimeRemoteObjectSubtypeSet
- | RuntimeRemoteObjectSubtypeWeakmap
- | RuntimeRemoteObjectSubtypeWeakset
- | RuntimeRemoteObjectSubtypeIterator
- | RuntimeRemoteObjectSubtypeGenerator
- | RuntimeRemoteObjectSubtypeError
- | RuntimeRemoteObjectSubtypeProxy
- | RuntimeRemoteObjectSubtypePromise
- | RuntimeRemoteObjectSubtypeTypedarray
- | RuntimeRemoteObjectSubtypeArraybuffer
- | RuntimeRemoteObjectSubtypeDataview
- | RuntimeRemoteObjectSubtypeWebassemblymemory
- | RuntimeRemoteObjectSubtypeWasmvalue
- data RuntimeRemoteObjectType
- type RuntimeUnserializableValue = Text
- type RuntimeRemoteObjectId = Text
- data RuntimeWebDriverValue = RuntimeWebDriverValue {}
- data RuntimeWebDriverValueType
- = RuntimeWebDriverValueTypeUndefined
- | RuntimeWebDriverValueTypeNull
- | RuntimeWebDriverValueTypeString
- | RuntimeWebDriverValueTypeNumber
- | RuntimeWebDriverValueTypeBoolean
- | RuntimeWebDriverValueTypeBigint
- | RuntimeWebDriverValueTypeRegexp
- | RuntimeWebDriverValueTypeDate
- | RuntimeWebDriverValueTypeSymbol
- | RuntimeWebDriverValueTypeArray
- | RuntimeWebDriverValueTypeObject
- | RuntimeWebDriverValueTypeFunction
- | RuntimeWebDriverValueTypeMap
- | RuntimeWebDriverValueTypeSet
- | RuntimeWebDriverValueTypeWeakmap
- | RuntimeWebDriverValueTypeWeakset
- | RuntimeWebDriverValueTypeError
- | RuntimeWebDriverValueTypeProxy
- | RuntimeWebDriverValueTypePromise
- | RuntimeWebDriverValueTypeTypedarray
- | RuntimeWebDriverValueTypeArraybuffer
- | RuntimeWebDriverValueTypeNode
- | RuntimeWebDriverValueTypeWindow
- type RuntimeScriptId = Text
- pRuntimeAwaitPromise :: RuntimeRemoteObjectId -> PRuntimeAwaitPromise
- pRuntimeCallFunctionOn :: Text -> PRuntimeCallFunctionOn
- pRuntimeCompileScript :: Text -> Text -> Bool -> PRuntimeCompileScript
- pRuntimeDisable :: PRuntimeDisable
- pRuntimeDiscardConsoleEntries :: PRuntimeDiscardConsoleEntries
- pRuntimeEnable :: PRuntimeEnable
- pRuntimeEvaluate :: Text -> PRuntimeEvaluate
- pRuntimeGetIsolateId :: PRuntimeGetIsolateId
- pRuntimeGetHeapUsage :: PRuntimeGetHeapUsage
- pRuntimeGetProperties :: RuntimeRemoteObjectId -> PRuntimeGetProperties
- pRuntimeGlobalLexicalScopeNames :: PRuntimeGlobalLexicalScopeNames
- pRuntimeQueryObjects :: RuntimeRemoteObjectId -> PRuntimeQueryObjects
- pRuntimeReleaseObject :: RuntimeRemoteObjectId -> PRuntimeReleaseObject
- pRuntimeReleaseObjectGroup :: Text -> PRuntimeReleaseObjectGroup
- pRuntimeRunIfWaitingForDebugger :: PRuntimeRunIfWaitingForDebugger
- pRuntimeRunScript :: RuntimeScriptId -> PRuntimeRunScript
- pRuntimeSetAsyncCallStackDepth :: Int -> PRuntimeSetAsyncCallStackDepth
- pRuntimeSetCustomObjectFormatterEnabled :: Bool -> PRuntimeSetCustomObjectFormatterEnabled
- pRuntimeSetMaxCallStackSizeToCapture :: Int -> PRuntimeSetMaxCallStackSizeToCapture
- pRuntimeTerminateExecution :: PRuntimeTerminateExecution
- pRuntimeAddBinding :: Text -> PRuntimeAddBinding
- pRuntimeRemoveBinding :: Text -> PRuntimeRemoveBinding
- pRuntimeGetExceptionDetails :: RuntimeRemoteObjectId -> PRuntimeGetExceptionDetails
Documentation
data RuntimeGetExceptionDetails Source #
Constructors
RuntimeGetExceptionDetails | |
Instances
Eq RuntimeGetExceptionDetails Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeGetExceptionDetails -> RuntimeGetExceptionDetails -> Bool # (/=) :: RuntimeGetExceptionDetails -> RuntimeGetExceptionDetails -> Bool # | |
Show RuntimeGetExceptionDetails Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeGetExceptionDetails -> ShowS # show :: RuntimeGetExceptionDetails -> String # showList :: [RuntimeGetExceptionDetails] -> ShowS # | |
FromJSON RuntimeGetExceptionDetails Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeGetExceptionDetails # parseJSONList :: Value -> Parser [RuntimeGetExceptionDetails] # |
data PRuntimeGetExceptionDetails Source #
This method tries to lookup and populate exception details for a JavaScript Error object. Note that the stackTrace portion of the resulting exceptionDetails will only be populated if the Runtime domain was enabled at the time when the Error was thrown.
Parameters of the getExceptionDetails
command.
Constructors
PRuntimeGetExceptionDetails | |
Fields
|
Instances
Eq PRuntimeGetExceptionDetails Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: PRuntimeGetExceptionDetails -> PRuntimeGetExceptionDetails -> Bool # (/=) :: PRuntimeGetExceptionDetails -> PRuntimeGetExceptionDetails -> Bool # | |
Show PRuntimeGetExceptionDetails Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeGetExceptionDetails -> ShowS # show :: PRuntimeGetExceptionDetails -> String # showList :: [PRuntimeGetExceptionDetails] -> ShowS # | |
ToJSON PRuntimeGetExceptionDetails Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: PRuntimeGetExceptionDetails -> Value # toEncoding :: PRuntimeGetExceptionDetails -> Encoding # toJSONList :: [PRuntimeGetExceptionDetails] -> Value # toEncodingList :: [PRuntimeGetExceptionDetails] -> Encoding # | |
Command PRuntimeGetExceptionDetails Source # | |
Defined in CDP.Domains.Runtime Associated Types | |
type CommandResponse PRuntimeGetExceptionDetails Source # | |
data PRuntimeRemoveBinding Source #
This method does not remove binding function from global object but unsubscribes current runtime agent from Runtime.bindingCalled notifications.
Parameters of the removeBinding
command.
Constructors
PRuntimeRemoveBinding | |
Fields |
Instances
data PRuntimeAddBinding Source #
If executionContextId is empty, adds binding with the given name on the global objects of all inspected contexts, including those created later, bindings survive reloads. Binding function takes exactly one argument, this argument should be string, in case of any other input, function throws an exception. Each binding function call produces Runtime.bindingCalled notification.
Parameters of the addBinding
command.
Constructors
PRuntimeAddBinding | |
Fields
|
Instances
Eq PRuntimeAddBinding Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: PRuntimeAddBinding -> PRuntimeAddBinding -> Bool # (/=) :: PRuntimeAddBinding -> PRuntimeAddBinding -> Bool # | |
Show PRuntimeAddBinding Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeAddBinding -> ShowS # show :: PRuntimeAddBinding -> String # showList :: [PRuntimeAddBinding] -> ShowS # | |
ToJSON PRuntimeAddBinding Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: PRuntimeAddBinding -> Value # toEncoding :: PRuntimeAddBinding -> Encoding # toJSONList :: [PRuntimeAddBinding] -> Value # toEncodingList :: [PRuntimeAddBinding] -> Encoding # | |
Command PRuntimeAddBinding Source # | |
Defined in CDP.Domains.Runtime Associated Types Methods commandName :: Proxy PRuntimeAddBinding -> String Source # fromJSON :: Proxy PRuntimeAddBinding -> Value -> Result (CommandResponse PRuntimeAddBinding) Source # | |
type CommandResponse PRuntimeAddBinding Source # | |
Defined in CDP.Domains.Runtime |
data PRuntimeTerminateExecution Source #
Terminate current or next JavaScript execution. Will cancel the termination when the outer-most script execution ends.
Parameters of the terminateExecution
command.
Constructors
PRuntimeTerminateExecution |
Instances
Eq PRuntimeTerminateExecution Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: PRuntimeTerminateExecution -> PRuntimeTerminateExecution -> Bool # (/=) :: PRuntimeTerminateExecution -> PRuntimeTerminateExecution -> Bool # | |
Show PRuntimeTerminateExecution Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeTerminateExecution -> ShowS # show :: PRuntimeTerminateExecution -> String # showList :: [PRuntimeTerminateExecution] -> ShowS # | |
ToJSON PRuntimeTerminateExecution Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: PRuntimeTerminateExecution -> Value # toEncoding :: PRuntimeTerminateExecution -> Encoding # toJSONList :: [PRuntimeTerminateExecution] -> Value # toEncodingList :: [PRuntimeTerminateExecution] -> Encoding # | |
Command PRuntimeTerminateExecution Source # | |
Defined in CDP.Domains.Runtime Associated Types | |
type CommandResponse PRuntimeTerminateExecution Source # | |
Defined in CDP.Domains.Runtime |
data PRuntimeSetMaxCallStackSizeToCapture Source #
Parameters of the setMaxCallStackSizeToCapture
command.
Constructors
PRuntimeSetMaxCallStackSizeToCapture | |
Instances
Eq PRuntimeSetMaxCallStackSizeToCapture Source # | |
Show PRuntimeSetMaxCallStackSizeToCapture Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeSetMaxCallStackSizeToCapture -> ShowS # show :: PRuntimeSetMaxCallStackSizeToCapture -> String # showList :: [PRuntimeSetMaxCallStackSizeToCapture] -> ShowS # | |
ToJSON PRuntimeSetMaxCallStackSizeToCapture Source # | |
Defined in CDP.Domains.Runtime | |
Command PRuntimeSetMaxCallStackSizeToCapture Source # | |
Defined in CDP.Domains.Runtime Associated Types type CommandResponse PRuntimeSetMaxCallStackSizeToCapture Source # | |
type CommandResponse PRuntimeSetMaxCallStackSizeToCapture Source # | |
Defined in CDP.Domains.Runtime |
data PRuntimeSetCustomObjectFormatterEnabled Source #
Parameters of the setCustomObjectFormatterEnabled
command.
Constructors
PRuntimeSetCustomObjectFormatterEnabled | |
Instances
data PRuntimeSetAsyncCallStackDepth Source #
Enables or disables async call stacks tracking.
Parameters of the setAsyncCallStackDepth
command.
Constructors
PRuntimeSetAsyncCallStackDepth | |
Fields
|
Instances
Eq PRuntimeSetAsyncCallStackDepth Source # | |
Defined in CDP.Domains.Runtime | |
Show PRuntimeSetAsyncCallStackDepth Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeSetAsyncCallStackDepth -> ShowS # show :: PRuntimeSetAsyncCallStackDepth -> String # showList :: [PRuntimeSetAsyncCallStackDepth] -> ShowS # | |
ToJSON PRuntimeSetAsyncCallStackDepth Source # | |
Defined in CDP.Domains.Runtime | |
Command PRuntimeSetAsyncCallStackDepth Source # | |
Defined in CDP.Domains.Runtime Associated Types type CommandResponse PRuntimeSetAsyncCallStackDepth Source # | |
type CommandResponse PRuntimeSetAsyncCallStackDepth Source # | |
Defined in CDP.Domains.Runtime |
data RuntimeRunScript Source #
Constructors
RuntimeRunScript | |
Fields
|
Instances
Eq RuntimeRunScript Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeRunScript -> RuntimeRunScript -> Bool # (/=) :: RuntimeRunScript -> RuntimeRunScript -> Bool # | |
Show RuntimeRunScript Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeRunScript -> ShowS # show :: RuntimeRunScript -> String # showList :: [RuntimeRunScript] -> ShowS # | |
FromJSON RuntimeRunScript Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeRunScript # parseJSONList :: Value -> Parser [RuntimeRunScript] # |
data PRuntimeRunScript Source #
Runs script with given id in a given context.
Parameters of the runScript
command.
Constructors
PRuntimeRunScript | |
Fields
|
Instances
Eq PRuntimeRunScript Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: PRuntimeRunScript -> PRuntimeRunScript -> Bool # (/=) :: PRuntimeRunScript -> PRuntimeRunScript -> Bool # | |
Show PRuntimeRunScript Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeRunScript -> ShowS # show :: PRuntimeRunScript -> String # showList :: [PRuntimeRunScript] -> ShowS # | |
ToJSON PRuntimeRunScript Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: PRuntimeRunScript -> Value # toEncoding :: PRuntimeRunScript -> Encoding # toJSONList :: [PRuntimeRunScript] -> Value # toEncodingList :: [PRuntimeRunScript] -> Encoding # | |
Command PRuntimeRunScript Source # | |
Defined in CDP.Domains.Runtime Associated Types Methods commandName :: Proxy PRuntimeRunScript -> String Source # fromJSON :: Proxy PRuntimeRunScript -> Value -> Result (CommandResponse PRuntimeRunScript) Source # | |
type CommandResponse PRuntimeRunScript Source # | |
Defined in CDP.Domains.Runtime |
data PRuntimeRunIfWaitingForDebugger Source #
Tells inspected instance to run if it was waiting for debugger to attach.
Parameters of the runIfWaitingForDebugger
command.
Constructors
PRuntimeRunIfWaitingForDebugger |
Instances
Eq PRuntimeRunIfWaitingForDebugger Source # | |
Defined in CDP.Domains.Runtime | |
Show PRuntimeRunIfWaitingForDebugger Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeRunIfWaitingForDebugger -> ShowS # | |
ToJSON PRuntimeRunIfWaitingForDebugger Source # | |
Defined in CDP.Domains.Runtime | |
Command PRuntimeRunIfWaitingForDebugger Source # | |
Defined in CDP.Domains.Runtime Associated Types type CommandResponse PRuntimeRunIfWaitingForDebugger Source # | |
type CommandResponse PRuntimeRunIfWaitingForDebugger Source # | |
Defined in CDP.Domains.Runtime |
data PRuntimeReleaseObjectGroup Source #
Releases all remote objects that belong to a given group.
Parameters of the releaseObjectGroup
command.
Constructors
PRuntimeReleaseObjectGroup | |
Fields
|
Instances
Eq PRuntimeReleaseObjectGroup Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: PRuntimeReleaseObjectGroup -> PRuntimeReleaseObjectGroup -> Bool # (/=) :: PRuntimeReleaseObjectGroup -> PRuntimeReleaseObjectGroup -> Bool # | |
Show PRuntimeReleaseObjectGroup Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeReleaseObjectGroup -> ShowS # show :: PRuntimeReleaseObjectGroup -> String # showList :: [PRuntimeReleaseObjectGroup] -> ShowS # | |
ToJSON PRuntimeReleaseObjectGroup Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: PRuntimeReleaseObjectGroup -> Value # toEncoding :: PRuntimeReleaseObjectGroup -> Encoding # toJSONList :: [PRuntimeReleaseObjectGroup] -> Value # toEncodingList :: [PRuntimeReleaseObjectGroup] -> Encoding # | |
Command PRuntimeReleaseObjectGroup Source # | |
Defined in CDP.Domains.Runtime Associated Types | |
type CommandResponse PRuntimeReleaseObjectGroup Source # | |
Defined in CDP.Domains.Runtime |
data PRuntimeReleaseObject Source #
Releases remote object with given id.
Parameters of the releaseObject
command.
Constructors
PRuntimeReleaseObject | |
Fields
|
Instances
data RuntimeQueryObjects Source #
Constructors
RuntimeQueryObjects | |
Fields
|
Instances
Eq RuntimeQueryObjects Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeQueryObjects -> RuntimeQueryObjects -> Bool # (/=) :: RuntimeQueryObjects -> RuntimeQueryObjects -> Bool # | |
Show RuntimeQueryObjects Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeQueryObjects -> ShowS # show :: RuntimeQueryObjects -> String # showList :: [RuntimeQueryObjects] -> ShowS # | |
FromJSON RuntimeQueryObjects Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeQueryObjects # parseJSONList :: Value -> Parser [RuntimeQueryObjects] # |
data PRuntimeQueryObjects Source #
Parameters of the queryObjects
command.
Constructors
PRuntimeQueryObjects | |
Fields
|
Instances
data RuntimeGlobalLexicalScopeNames Source #
Constructors
RuntimeGlobalLexicalScopeNames | |
Fields |
Instances
Eq RuntimeGlobalLexicalScopeNames Source # | |
Defined in CDP.Domains.Runtime | |
Show RuntimeGlobalLexicalScopeNames Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeGlobalLexicalScopeNames -> ShowS # show :: RuntimeGlobalLexicalScopeNames -> String # showList :: [RuntimeGlobalLexicalScopeNames] -> ShowS # | |
FromJSON RuntimeGlobalLexicalScopeNames Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeGlobalLexicalScopeNames # parseJSONList :: Value -> Parser [RuntimeGlobalLexicalScopeNames] # |
data PRuntimeGlobalLexicalScopeNames Source #
Returns all let, const and class variables from global scope.
Parameters of the globalLexicalScopeNames
command.
Constructors
PRuntimeGlobalLexicalScopeNames | |
Fields
|
Instances
Eq PRuntimeGlobalLexicalScopeNames Source # | |
Defined in CDP.Domains.Runtime | |
Show PRuntimeGlobalLexicalScopeNames Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeGlobalLexicalScopeNames -> ShowS # | |
ToJSON PRuntimeGlobalLexicalScopeNames Source # | |
Defined in CDP.Domains.Runtime | |
Command PRuntimeGlobalLexicalScopeNames Source # | |
Defined in CDP.Domains.Runtime Associated Types type CommandResponse PRuntimeGlobalLexicalScopeNames Source # | |
type CommandResponse PRuntimeGlobalLexicalScopeNames Source # | |
data RuntimeGetProperties Source #
Constructors
RuntimeGetProperties | |
Fields
|
Instances
Eq RuntimeGetProperties Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeGetProperties -> RuntimeGetProperties -> Bool # (/=) :: RuntimeGetProperties -> RuntimeGetProperties -> Bool # | |
Show RuntimeGetProperties Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeGetProperties -> ShowS # show :: RuntimeGetProperties -> String # showList :: [RuntimeGetProperties] -> ShowS # | |
FromJSON RuntimeGetProperties Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeGetProperties # parseJSONList :: Value -> Parser [RuntimeGetProperties] # |
data PRuntimeGetProperties Source #
Returns properties of a given object. Object group of the result is inherited from the target object.
Parameters of the getProperties
command.
Constructors
PRuntimeGetProperties | |
Fields
|
Instances
data RuntimeGetHeapUsage Source #
Constructors
RuntimeGetHeapUsage | |
Fields
|
Instances
Eq RuntimeGetHeapUsage Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeGetHeapUsage -> RuntimeGetHeapUsage -> Bool # (/=) :: RuntimeGetHeapUsage -> RuntimeGetHeapUsage -> Bool # | |
Show RuntimeGetHeapUsage Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeGetHeapUsage -> ShowS # show :: RuntimeGetHeapUsage -> String # showList :: [RuntimeGetHeapUsage] -> ShowS # | |
FromJSON RuntimeGetHeapUsage Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeGetHeapUsage # parseJSONList :: Value -> Parser [RuntimeGetHeapUsage] # |
data PRuntimeGetHeapUsage Source #
Returns the JavaScript heap usage. It is the total usage of the corresponding isolate not scoped to a particular Runtime.
Parameters of the getHeapUsage
command.
Constructors
PRuntimeGetHeapUsage |
Instances
data RuntimeGetIsolateId Source #
Constructors
RuntimeGetIsolateId | |
Fields
|
Instances
Eq RuntimeGetIsolateId Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeGetIsolateId -> RuntimeGetIsolateId -> Bool # (/=) :: RuntimeGetIsolateId -> RuntimeGetIsolateId -> Bool # | |
Show RuntimeGetIsolateId Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeGetIsolateId -> ShowS # show :: RuntimeGetIsolateId -> String # showList :: [RuntimeGetIsolateId] -> ShowS # | |
FromJSON RuntimeGetIsolateId Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeGetIsolateId # parseJSONList :: Value -> Parser [RuntimeGetIsolateId] # |
data PRuntimeGetIsolateId Source #
Returns the isolate id.
Parameters of the getIsolateId
command.
Constructors
PRuntimeGetIsolateId |
Instances
data RuntimeEvaluate Source #
Constructors
RuntimeEvaluate | |
Fields
|
Instances
Eq RuntimeEvaluate Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeEvaluate -> RuntimeEvaluate -> Bool # (/=) :: RuntimeEvaluate -> RuntimeEvaluate -> Bool # | |
Show RuntimeEvaluate Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeEvaluate -> ShowS # show :: RuntimeEvaluate -> String # showList :: [RuntimeEvaluate] -> ShowS # | |
FromJSON RuntimeEvaluate Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeEvaluate # parseJSONList :: Value -> Parser [RuntimeEvaluate] # |
data PRuntimeEvaluate Source #
Evaluates expression on global object.
Parameters of the evaluate
command.
Constructors
PRuntimeEvaluate | |
Fields
|
Instances
Eq PRuntimeEvaluate Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: PRuntimeEvaluate -> PRuntimeEvaluate -> Bool # (/=) :: PRuntimeEvaluate -> PRuntimeEvaluate -> Bool # | |
Show PRuntimeEvaluate Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeEvaluate -> ShowS # show :: PRuntimeEvaluate -> String # showList :: [PRuntimeEvaluate] -> ShowS # | |
ToJSON PRuntimeEvaluate Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: PRuntimeEvaluate -> Value # toEncoding :: PRuntimeEvaluate -> Encoding # toJSONList :: [PRuntimeEvaluate] -> Value # toEncodingList :: [PRuntimeEvaluate] -> Encoding # | |
Command PRuntimeEvaluate Source # | |
Defined in CDP.Domains.Runtime Associated Types Methods commandName :: Proxy PRuntimeEvaluate -> String Source # fromJSON :: Proxy PRuntimeEvaluate -> Value -> Result (CommandResponse PRuntimeEvaluate) Source # | |
type CommandResponse PRuntimeEvaluate Source # | |
Defined in CDP.Domains.Runtime |
data PRuntimeEnable Source #
Enables reporting of execution contexts creation by means of executionContextCreated
event.
When the reporting gets enabled the event will be sent immediately for each existing execution
context.
Parameters of the enable
command.
Constructors
PRuntimeEnable |
Instances
Eq PRuntimeEnable Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: PRuntimeEnable -> PRuntimeEnable -> Bool # (/=) :: PRuntimeEnable -> PRuntimeEnable -> Bool # | |
Show PRuntimeEnable Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeEnable -> ShowS # show :: PRuntimeEnable -> String # showList :: [PRuntimeEnable] -> ShowS # | |
ToJSON PRuntimeEnable Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: PRuntimeEnable -> Value # toEncoding :: PRuntimeEnable -> Encoding # toJSONList :: [PRuntimeEnable] -> Value # toEncodingList :: [PRuntimeEnable] -> Encoding # | |
Command PRuntimeEnable Source # | |
Defined in CDP.Domains.Runtime Associated Types Methods commandName :: Proxy PRuntimeEnable -> String Source # fromJSON :: Proxy PRuntimeEnable -> Value -> Result (CommandResponse PRuntimeEnable) Source # | |
type CommandResponse PRuntimeEnable Source # | |
Defined in CDP.Domains.Runtime |
data PRuntimeDiscardConsoleEntries Source #
Discards collected exceptions and console API calls.
Parameters of the discardConsoleEntries
command.
Constructors
PRuntimeDiscardConsoleEntries |
Instances
Eq PRuntimeDiscardConsoleEntries Source # | |
Defined in CDP.Domains.Runtime | |
Show PRuntimeDiscardConsoleEntries Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeDiscardConsoleEntries -> ShowS # show :: PRuntimeDiscardConsoleEntries -> String # showList :: [PRuntimeDiscardConsoleEntries] -> ShowS # | |
ToJSON PRuntimeDiscardConsoleEntries Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: PRuntimeDiscardConsoleEntries -> Value # toEncoding :: PRuntimeDiscardConsoleEntries -> Encoding # toJSONList :: [PRuntimeDiscardConsoleEntries] -> Value # toEncodingList :: [PRuntimeDiscardConsoleEntries] -> Encoding # | |
Command PRuntimeDiscardConsoleEntries Source # | |
Defined in CDP.Domains.Runtime Associated Types | |
type CommandResponse PRuntimeDiscardConsoleEntries Source # | |
Defined in CDP.Domains.Runtime |
data PRuntimeDisable Source #
Disables reporting of execution contexts creation.
Parameters of the disable
command.
Constructors
PRuntimeDisable |
Instances
Eq PRuntimeDisable Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: PRuntimeDisable -> PRuntimeDisable -> Bool # (/=) :: PRuntimeDisable -> PRuntimeDisable -> Bool # | |
Show PRuntimeDisable Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeDisable -> ShowS # show :: PRuntimeDisable -> String # showList :: [PRuntimeDisable] -> ShowS # | |
ToJSON PRuntimeDisable Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: PRuntimeDisable -> Value # toEncoding :: PRuntimeDisable -> Encoding # toJSONList :: [PRuntimeDisable] -> Value # toEncodingList :: [PRuntimeDisable] -> Encoding # | |
Command PRuntimeDisable Source # | |
Defined in CDP.Domains.Runtime Associated Types Methods commandName :: Proxy PRuntimeDisable -> String Source # fromJSON :: Proxy PRuntimeDisable -> Value -> Result (CommandResponse PRuntimeDisable) Source # | |
type CommandResponse PRuntimeDisable Source # | |
Defined in CDP.Domains.Runtime |
data RuntimeCompileScript Source #
Constructors
RuntimeCompileScript | |
Fields
|
Instances
Eq RuntimeCompileScript Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeCompileScript -> RuntimeCompileScript -> Bool # (/=) :: RuntimeCompileScript -> RuntimeCompileScript -> Bool # | |
Show RuntimeCompileScript Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeCompileScript -> ShowS # show :: RuntimeCompileScript -> String # showList :: [RuntimeCompileScript] -> ShowS # | |
FromJSON RuntimeCompileScript Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeCompileScript # parseJSONList :: Value -> Parser [RuntimeCompileScript] # |
data PRuntimeCompileScript Source #
Compiles expression.
Parameters of the compileScript
command.
Constructors
PRuntimeCompileScript | |
Fields
|
Instances
data RuntimeCallFunctionOn Source #
Constructors
RuntimeCallFunctionOn | |
Fields
|
Instances
Eq RuntimeCallFunctionOn Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeCallFunctionOn -> RuntimeCallFunctionOn -> Bool # (/=) :: RuntimeCallFunctionOn -> RuntimeCallFunctionOn -> Bool # | |
Show RuntimeCallFunctionOn Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeCallFunctionOn -> ShowS # show :: RuntimeCallFunctionOn -> String # showList :: [RuntimeCallFunctionOn] -> ShowS # | |
FromJSON RuntimeCallFunctionOn Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeCallFunctionOn # parseJSONList :: Value -> Parser [RuntimeCallFunctionOn] # |
data PRuntimeCallFunctionOn Source #
Calls function with given declaration on the given object. Object group of the result is inherited from the target object.
Parameters of the callFunctionOn
command.
Constructors
PRuntimeCallFunctionOn | |
Fields
|
Instances
Eq PRuntimeCallFunctionOn Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: PRuntimeCallFunctionOn -> PRuntimeCallFunctionOn -> Bool # (/=) :: PRuntimeCallFunctionOn -> PRuntimeCallFunctionOn -> Bool # | |
Show PRuntimeCallFunctionOn Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> PRuntimeCallFunctionOn -> ShowS # show :: PRuntimeCallFunctionOn -> String # showList :: [PRuntimeCallFunctionOn] -> ShowS # | |
ToJSON PRuntimeCallFunctionOn Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: PRuntimeCallFunctionOn -> Value # toEncoding :: PRuntimeCallFunctionOn -> Encoding # toJSONList :: [PRuntimeCallFunctionOn] -> Value # | |
Command PRuntimeCallFunctionOn Source # | |
Defined in CDP.Domains.Runtime Associated Types Methods commandName :: Proxy PRuntimeCallFunctionOn -> String Source # fromJSON :: Proxy PRuntimeCallFunctionOn -> Value -> Result (CommandResponse PRuntimeCallFunctionOn) Source # | |
type CommandResponse PRuntimeCallFunctionOn Source # | |
Defined in CDP.Domains.Runtime |
data RuntimeAwaitPromise Source #
Constructors
RuntimeAwaitPromise | |
Fields
|
Instances
Eq RuntimeAwaitPromise Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeAwaitPromise -> RuntimeAwaitPromise -> Bool # (/=) :: RuntimeAwaitPromise -> RuntimeAwaitPromise -> Bool # | |
Show RuntimeAwaitPromise Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeAwaitPromise -> ShowS # show :: RuntimeAwaitPromise -> String # showList :: [RuntimeAwaitPromise] -> ShowS # | |
FromJSON RuntimeAwaitPromise Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeAwaitPromise # parseJSONList :: Value -> Parser [RuntimeAwaitPromise] # |
data PRuntimeAwaitPromise Source #
Add handler to promise with given promise object id.
Parameters of the awaitPromise
command.
Constructors
PRuntimeAwaitPromise | |
Fields
|
Instances
data RuntimeInspectRequested Source #
Type of the inspectRequested
event.
Constructors
RuntimeInspectRequested | |
Fields
|
Instances
Eq RuntimeInspectRequested Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeInspectRequested -> RuntimeInspectRequested -> Bool # (/=) :: RuntimeInspectRequested -> RuntimeInspectRequested -> Bool # | |
Show RuntimeInspectRequested Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeInspectRequested -> ShowS # show :: RuntimeInspectRequested -> String # showList :: [RuntimeInspectRequested] -> ShowS # | |
FromJSON RuntimeInspectRequested Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeInspectRequested # parseJSONList :: Value -> Parser [RuntimeInspectRequested] # | |
Event RuntimeInspectRequested Source # | |
Defined in CDP.Domains.Runtime |
data RuntimeExecutionContextsCleared Source #
Type of the executionContextsCleared
event.
Constructors
RuntimeExecutionContextsCleared |
Instances
Eq RuntimeExecutionContextsCleared Source # | |
Defined in CDP.Domains.Runtime | |
Read RuntimeExecutionContextsCleared Source # | |
Show RuntimeExecutionContextsCleared Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeExecutionContextsCleared -> ShowS # | |
FromJSON RuntimeExecutionContextsCleared Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeExecutionContextsCleared # parseJSONList :: Value -> Parser [RuntimeExecutionContextsCleared] # | |
Event RuntimeExecutionContextsCleared Source # | |
Defined in CDP.Domains.Runtime |
data RuntimeExecutionContextDestroyed Source #
Type of the executionContextDestroyed
event.
Constructors
RuntimeExecutionContextDestroyed | |
Fields
|
Instances
Eq RuntimeExecutionContextDestroyed Source # | |
Defined in CDP.Domains.Runtime | |
Show RuntimeExecutionContextDestroyed Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeExecutionContextDestroyed -> ShowS # | |
FromJSON RuntimeExecutionContextDestroyed Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeExecutionContextDestroyed # parseJSONList :: Value -> Parser [RuntimeExecutionContextDestroyed] # | |
Event RuntimeExecutionContextDestroyed Source # | |
Defined in CDP.Domains.Runtime |
data RuntimeExecutionContextCreated Source #
Type of the executionContextCreated
event.
Constructors
RuntimeExecutionContextCreated | |
Fields
|
Instances
Eq RuntimeExecutionContextCreated Source # | |
Defined in CDP.Domains.Runtime | |
Show RuntimeExecutionContextCreated Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeExecutionContextCreated -> ShowS # show :: RuntimeExecutionContextCreated -> String # showList :: [RuntimeExecutionContextCreated] -> ShowS # | |
FromJSON RuntimeExecutionContextCreated Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeExecutionContextCreated # parseJSONList :: Value -> Parser [RuntimeExecutionContextCreated] # | |
Event RuntimeExecutionContextCreated Source # | |
Defined in CDP.Domains.Runtime |
data RuntimeExceptionThrown Source #
Type of the exceptionThrown
event.
Constructors
RuntimeExceptionThrown | |
Fields
|
Instances
Eq RuntimeExceptionThrown Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeExceptionThrown -> RuntimeExceptionThrown -> Bool # (/=) :: RuntimeExceptionThrown -> RuntimeExceptionThrown -> Bool # | |
Show RuntimeExceptionThrown Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeExceptionThrown -> ShowS # show :: RuntimeExceptionThrown -> String # showList :: [RuntimeExceptionThrown] -> ShowS # | |
FromJSON RuntimeExceptionThrown Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeExceptionThrown # parseJSONList :: Value -> Parser [RuntimeExceptionThrown] # | |
Event RuntimeExceptionThrown Source # | |
Defined in CDP.Domains.Runtime |
data RuntimeExceptionRevoked Source #
Type of the exceptionRevoked
event.
Constructors
RuntimeExceptionRevoked | |
Fields
|
Instances
Eq RuntimeExceptionRevoked Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeExceptionRevoked -> RuntimeExceptionRevoked -> Bool # (/=) :: RuntimeExceptionRevoked -> RuntimeExceptionRevoked -> Bool # | |
Show RuntimeExceptionRevoked Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeExceptionRevoked -> ShowS # show :: RuntimeExceptionRevoked -> String # showList :: [RuntimeExceptionRevoked] -> ShowS # | |
FromJSON RuntimeExceptionRevoked Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeExceptionRevoked # parseJSONList :: Value -> Parser [RuntimeExceptionRevoked] # | |
Event RuntimeExceptionRevoked Source # | |
Defined in CDP.Domains.Runtime |
data RuntimeConsoleAPICalled Source #
Constructors
RuntimeConsoleAPICalled | |
Fields
|
Instances
Eq RuntimeConsoleAPICalled Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeConsoleAPICalled -> RuntimeConsoleAPICalled -> Bool # (/=) :: RuntimeConsoleAPICalled -> RuntimeConsoleAPICalled -> Bool # | |
Show RuntimeConsoleAPICalled Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeConsoleAPICalled -> ShowS # show :: RuntimeConsoleAPICalled -> String # showList :: [RuntimeConsoleAPICalled] -> ShowS # | |
FromJSON RuntimeConsoleAPICalled Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeConsoleAPICalled # parseJSONList :: Value -> Parser [RuntimeConsoleAPICalled] # | |
Event RuntimeConsoleAPICalled Source # | |
Defined in CDP.Domains.Runtime |
data RuntimeConsoleAPICalledType Source #
Type of the consoleAPICalled
event.
Constructors
Instances
data RuntimeBindingCalled Source #
Type of the bindingCalled
event.
Constructors
RuntimeBindingCalled | |
Fields
|
Instances
Eq RuntimeBindingCalled Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeBindingCalled -> RuntimeBindingCalled -> Bool # (/=) :: RuntimeBindingCalled -> RuntimeBindingCalled -> Bool # | |
Show RuntimeBindingCalled Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeBindingCalled -> ShowS # show :: RuntimeBindingCalled -> String # showList :: [RuntimeBindingCalled] -> ShowS # | |
FromJSON RuntimeBindingCalled Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeBindingCalled # parseJSONList :: Value -> Parser [RuntimeBindingCalled] # | |
Event RuntimeBindingCalled Source # | |
Defined in CDP.Domains.Runtime |
data RuntimeStackTraceId Source #
Type StackTraceId
.
If debuggerId
is set stack trace comes from another debugger and can be resolved there. This
allows to track cross-debugger calls. See StackTrace
and paused
for usages.
Constructors
RuntimeStackTraceId | |
Instances
Eq RuntimeStackTraceId Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeStackTraceId -> RuntimeStackTraceId -> Bool # (/=) :: RuntimeStackTraceId -> RuntimeStackTraceId -> Bool # | |
Show RuntimeStackTraceId Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeStackTraceId -> ShowS # show :: RuntimeStackTraceId -> String # showList :: [RuntimeStackTraceId] -> ShowS # | |
ToJSON RuntimeStackTraceId Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimeStackTraceId -> Value # toEncoding :: RuntimeStackTraceId -> Encoding # toJSONList :: [RuntimeStackTraceId] -> Value # toEncodingList :: [RuntimeStackTraceId] -> Encoding # | |
FromJSON RuntimeStackTraceId Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeStackTraceId # parseJSONList :: Value -> Parser [RuntimeStackTraceId] # |
type RuntimeUniqueDebuggerId = Text Source #
Type UniqueDebuggerId
.
Unique identifier of current debugger.
data RuntimeStackTrace Source #
Type StackTrace
.
Call frames for assertions or error messages.
Constructors
RuntimeStackTrace | |
Fields
|
Instances
Eq RuntimeStackTrace Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeStackTrace -> RuntimeStackTrace -> Bool # (/=) :: RuntimeStackTrace -> RuntimeStackTrace -> Bool # | |
Show RuntimeStackTrace Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeStackTrace -> ShowS # show :: RuntimeStackTrace -> String # showList :: [RuntimeStackTrace] -> ShowS # | |
ToJSON RuntimeStackTrace Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimeStackTrace -> Value # toEncoding :: RuntimeStackTrace -> Encoding # toJSONList :: [RuntimeStackTrace] -> Value # toEncodingList :: [RuntimeStackTrace] -> Encoding # | |
FromJSON RuntimeStackTrace Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeStackTrace # parseJSONList :: Value -> Parser [RuntimeStackTrace] # |
data RuntimeCallFrame Source #
Type CallFrame
.
Stack entry for runtime errors and assertions.
Constructors
RuntimeCallFrame | |
Fields
|
Instances
Eq RuntimeCallFrame Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeCallFrame -> RuntimeCallFrame -> Bool # (/=) :: RuntimeCallFrame -> RuntimeCallFrame -> Bool # | |
Show RuntimeCallFrame Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeCallFrame -> ShowS # show :: RuntimeCallFrame -> String # showList :: [RuntimeCallFrame] -> ShowS # | |
ToJSON RuntimeCallFrame Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimeCallFrame -> Value # toEncoding :: RuntimeCallFrame -> Encoding # toJSONList :: [RuntimeCallFrame] -> Value # toEncodingList :: [RuntimeCallFrame] -> Encoding # | |
FromJSON RuntimeCallFrame Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeCallFrame # parseJSONList :: Value -> Parser [RuntimeCallFrame] # |
type RuntimeTimeDelta = Double Source #
Type TimeDelta
.
Number of milliseconds.
type RuntimeTimestamp = Double Source #
Type Timestamp
.
Number of milliseconds since epoch.
data RuntimeExceptionDetails Source #
Type ExceptionDetails
.
Detailed information about exception (or error) that was thrown during script compilation or
execution.
Constructors
RuntimeExceptionDetails | |
Fields
|
Instances
Eq RuntimeExceptionDetails Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeExceptionDetails -> RuntimeExceptionDetails -> Bool # (/=) :: RuntimeExceptionDetails -> RuntimeExceptionDetails -> Bool # | |
Show RuntimeExceptionDetails Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeExceptionDetails -> ShowS # show :: RuntimeExceptionDetails -> String # showList :: [RuntimeExceptionDetails] -> ShowS # | |
ToJSON RuntimeExceptionDetails Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimeExceptionDetails -> Value # toEncoding :: RuntimeExceptionDetails -> Encoding # toJSONList :: [RuntimeExceptionDetails] -> Value # | |
FromJSON RuntimeExceptionDetails Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeExceptionDetails # parseJSONList :: Value -> Parser [RuntimeExceptionDetails] # |
data RuntimeExecutionContextDescription Source #
Type ExecutionContextDescription
.
Description of an isolated world.
Constructors
RuntimeExecutionContextDescription | |
Fields
|
Instances
Eq RuntimeExecutionContextDescription Source # | |
Defined in CDP.Domains.Runtime | |
Show RuntimeExecutionContextDescription Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeExecutionContextDescription -> ShowS # | |
ToJSON RuntimeExecutionContextDescription Source # | |
Defined in CDP.Domains.Runtime | |
FromJSON RuntimeExecutionContextDescription Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeExecutionContextDescription # parseJSONList :: Value -> Parser [RuntimeExecutionContextDescription] # |
type RuntimeExecutionContextId = Int Source #
Type ExecutionContextId
.
Id of an execution context.
data RuntimeCallArgument Source #
Type CallArgument
.
Represents function call argument. Either remote object id objectId
, primitive value
,
unserializable primitive value or neither of (for undefined) them should be specified.
Constructors
RuntimeCallArgument | |
Fields
|
Instances
Eq RuntimeCallArgument Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeCallArgument -> RuntimeCallArgument -> Bool # (/=) :: RuntimeCallArgument -> RuntimeCallArgument -> Bool # | |
Show RuntimeCallArgument Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeCallArgument -> ShowS # show :: RuntimeCallArgument -> String # showList :: [RuntimeCallArgument] -> ShowS # | |
ToJSON RuntimeCallArgument Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimeCallArgument -> Value # toEncoding :: RuntimeCallArgument -> Encoding # toJSONList :: [RuntimeCallArgument] -> Value # toEncodingList :: [RuntimeCallArgument] -> Encoding # | |
FromJSON RuntimeCallArgument Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeCallArgument # parseJSONList :: Value -> Parser [RuntimeCallArgument] # |
data RuntimePrivatePropertyDescriptor Source #
Type PrivatePropertyDescriptor
.
Object private field descriptor.
Constructors
RuntimePrivatePropertyDescriptor | |
Fields
|
Instances
Eq RuntimePrivatePropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime | |
Show RuntimePrivatePropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimePrivatePropertyDescriptor -> ShowS # | |
ToJSON RuntimePrivatePropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime | |
FromJSON RuntimePrivatePropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimePrivatePropertyDescriptor # parseJSONList :: Value -> Parser [RuntimePrivatePropertyDescriptor] # |
data RuntimeInternalPropertyDescriptor Source #
Type InternalPropertyDescriptor
.
Object internal property descriptor. This property isn't normally visible in JavaScript code.
Constructors
RuntimeInternalPropertyDescriptor | |
Fields
|
Instances
Eq RuntimeInternalPropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime | |
Show RuntimeInternalPropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeInternalPropertyDescriptor -> ShowS # | |
ToJSON RuntimeInternalPropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime | |
FromJSON RuntimeInternalPropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeInternalPropertyDescriptor # parseJSONList :: Value -> Parser [RuntimeInternalPropertyDescriptor] # |
data RuntimePropertyDescriptor Source #
Type PropertyDescriptor
.
Object property descriptor.
Constructors
RuntimePropertyDescriptor | |
Fields
|
Instances
Eq RuntimePropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimePropertyDescriptor -> RuntimePropertyDescriptor -> Bool # (/=) :: RuntimePropertyDescriptor -> RuntimePropertyDescriptor -> Bool # | |
Show RuntimePropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimePropertyDescriptor -> ShowS # show :: RuntimePropertyDescriptor -> String # showList :: [RuntimePropertyDescriptor] -> ShowS # | |
ToJSON RuntimePropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimePropertyDescriptor -> Value # toEncoding :: RuntimePropertyDescriptor -> Encoding # toJSONList :: [RuntimePropertyDescriptor] -> Value # | |
FromJSON RuntimePropertyDescriptor Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimePropertyDescriptor # parseJSONList :: Value -> Parser [RuntimePropertyDescriptor] # |
data RuntimeEntryPreview Source #
Type EntryPreview
.
Constructors
RuntimeEntryPreview | |
Fields
|
Instances
Eq RuntimeEntryPreview Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeEntryPreview -> RuntimeEntryPreview -> Bool # (/=) :: RuntimeEntryPreview -> RuntimeEntryPreview -> Bool # | |
Show RuntimeEntryPreview Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeEntryPreview -> ShowS # show :: RuntimeEntryPreview -> String # showList :: [RuntimeEntryPreview] -> ShowS # | |
ToJSON RuntimeEntryPreview Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimeEntryPreview -> Value # toEncoding :: RuntimeEntryPreview -> Encoding # toJSONList :: [RuntimeEntryPreview] -> Value # toEncodingList :: [RuntimeEntryPreview] -> Encoding # | |
FromJSON RuntimeEntryPreview Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeEntryPreview # parseJSONList :: Value -> Parser [RuntimeEntryPreview] # |
data RuntimePropertyPreview Source #
Constructors
RuntimePropertyPreview | |
Fields
|
Instances
Eq RuntimePropertyPreview Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimePropertyPreview -> RuntimePropertyPreview -> Bool # (/=) :: RuntimePropertyPreview -> RuntimePropertyPreview -> Bool # | |
Show RuntimePropertyPreview Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimePropertyPreview -> ShowS # show :: RuntimePropertyPreview -> String # showList :: [RuntimePropertyPreview] -> ShowS # | |
ToJSON RuntimePropertyPreview Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimePropertyPreview -> Value # toEncoding :: RuntimePropertyPreview -> Encoding # toJSONList :: [RuntimePropertyPreview] -> Value # | |
FromJSON RuntimePropertyPreview Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimePropertyPreview # parseJSONList :: Value -> Parser [RuntimePropertyPreview] # |
data RuntimePropertyPreviewSubtype Source #
Constructors
Instances
data RuntimePropertyPreviewType Source #
Type PropertyPreview
.
Constructors
Instances
data RuntimeObjectPreview Source #
Constructors
RuntimeObjectPreview | |
Fields
|
Instances
Eq RuntimeObjectPreview Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeObjectPreview -> RuntimeObjectPreview -> Bool # (/=) :: RuntimeObjectPreview -> RuntimeObjectPreview -> Bool # | |
Show RuntimeObjectPreview Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeObjectPreview -> ShowS # show :: RuntimeObjectPreview -> String # showList :: [RuntimeObjectPreview] -> ShowS # | |
ToJSON RuntimeObjectPreview Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimeObjectPreview -> Value # toEncoding :: RuntimeObjectPreview -> Encoding # toJSONList :: [RuntimeObjectPreview] -> Value # toEncodingList :: [RuntimeObjectPreview] -> Encoding # | |
FromJSON RuntimeObjectPreview Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeObjectPreview # parseJSONList :: Value -> Parser [RuntimeObjectPreview] # |
data RuntimeObjectPreviewSubtype Source #
Constructors
Instances
data RuntimeObjectPreviewType Source #
Type ObjectPreview
.
Object containing abbreviated remote object value.
Constructors
Instances
data RuntimeCustomPreview Source #
Type CustomPreview
.
Constructors
RuntimeCustomPreview | |
Fields
|
Instances
Eq RuntimeCustomPreview Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeCustomPreview -> RuntimeCustomPreview -> Bool # (/=) :: RuntimeCustomPreview -> RuntimeCustomPreview -> Bool # | |
Show RuntimeCustomPreview Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeCustomPreview -> ShowS # show :: RuntimeCustomPreview -> String # showList :: [RuntimeCustomPreview] -> ShowS # | |
ToJSON RuntimeCustomPreview Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimeCustomPreview -> Value # toEncoding :: RuntimeCustomPreview -> Encoding # toJSONList :: [RuntimeCustomPreview] -> Value # toEncodingList :: [RuntimeCustomPreview] -> Encoding # | |
FromJSON RuntimeCustomPreview Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeCustomPreview # parseJSONList :: Value -> Parser [RuntimeCustomPreview] # |
data RuntimeRemoteObject Source #
Constructors
RuntimeRemoteObject | |
Fields
|
Instances
Eq RuntimeRemoteObject Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeRemoteObject -> RuntimeRemoteObject -> Bool # (/=) :: RuntimeRemoteObject -> RuntimeRemoteObject -> Bool # | |
Show RuntimeRemoteObject Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeRemoteObject -> ShowS # show :: RuntimeRemoteObject -> String # showList :: [RuntimeRemoteObject] -> ShowS # | |
ToJSON RuntimeRemoteObject Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimeRemoteObject -> Value # toEncoding :: RuntimeRemoteObject -> Encoding # toJSONList :: [RuntimeRemoteObject] -> Value # toEncodingList :: [RuntimeRemoteObject] -> Encoding # | |
FromJSON RuntimeRemoteObject Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeRemoteObject # parseJSONList :: Value -> Parser [RuntimeRemoteObject] # |
data RuntimeRemoteObjectSubtype Source #
Constructors
Instances
data RuntimeRemoteObjectType Source #
Type RemoteObject
.
Mirror object referencing original JavaScript object.
Constructors
Instances
type RuntimeUnserializableValue = Text Source #
Type UnserializableValue
.
Primitive value which cannot be JSON-stringified. Includes values `-0`, NaN
, Infinity
,
`-Infinity`, and bigint literals.
type RuntimeRemoteObjectId = Text Source #
Type RemoteObjectId
.
Unique object identifier.
data RuntimeWebDriverValue Source #
Constructors
RuntimeWebDriverValue | |
Instances
Eq RuntimeWebDriverValue Source # | |
Defined in CDP.Domains.Runtime Methods (==) :: RuntimeWebDriverValue -> RuntimeWebDriverValue -> Bool # (/=) :: RuntimeWebDriverValue -> RuntimeWebDriverValue -> Bool # | |
Show RuntimeWebDriverValue Source # | |
Defined in CDP.Domains.Runtime Methods showsPrec :: Int -> RuntimeWebDriverValue -> ShowS # show :: RuntimeWebDriverValue -> String # showList :: [RuntimeWebDriverValue] -> ShowS # | |
ToJSON RuntimeWebDriverValue Source # | |
Defined in CDP.Domains.Runtime Methods toJSON :: RuntimeWebDriverValue -> Value # toEncoding :: RuntimeWebDriverValue -> Encoding # toJSONList :: [RuntimeWebDriverValue] -> Value # toEncodingList :: [RuntimeWebDriverValue] -> Encoding # | |
FromJSON RuntimeWebDriverValue Source # | |
Defined in CDP.Domains.Runtime Methods parseJSON :: Value -> Parser RuntimeWebDriverValue # parseJSONList :: Value -> Parser [RuntimeWebDriverValue] # |
data RuntimeWebDriverValueType Source #
Type WebDriverValue
.
Represents the value serialiazed by the WebDriver BiDi specification
https://w3c.github.io/webdriver-bidi.
Constructors
Instances
type RuntimeScriptId = Text Source #
Type ScriptId
.
Unique script identifier.
pRuntimeCompileScript :: Text -> Text -> Bool -> PRuntimeCompileScript Source #