{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ImplicitParams, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Types (
JSContextRef(..), JSM, askJSM, runJSM, MonadJSM(..), liftJSM
, DOMContext(..), DOM, askDOM, runDOM, MonadDOM(..), liftDOM
, JSVal(..), ToJSVal(..), FromJSVal(..), PToJSVal(..), PFromJSVal(..)
, integralToDoubleToJSVal, integralFromDoubleFromJSVal, integralFromDoubleFromJSValUnchecked
, JSString(..), ToJSString(..), FromJSString(..)
, toMaybeJSString, fromMaybeJSString
, noJSString
, fromJSArray, fromJSArrayUnchecked
, Object(..)
, Nullable(..), nullableToMaybe, maybeToNullable
, DOMString(..), ToDOMString(..), FromDOMString(..), IsDOMString, noDOMString
, USVString(..), IsUSVString, noUSVString
, ByteString(..), IsByteString, noByteString
, CSSOMString(..), IsCSSOMString, noCSSOMString
, maybeNullOrUndefined, maybeNullOrUndefined', GType(..)
, GObject(..), noGObject, IsGObject, toGObject, gTypeGObject, isA, objectToString
, castTo, unsafeCastTo, uncheckedCastTo
, strictEqual
, RawTypedArray(RawTypedArray), unRawTypedArray, IsRawTypedArray, toRawTypedArray, noRawTypedArray
, Function(Function), unFunction, IsFunction, toFunction, noFunction
, PromiseRejected(..), noPromiseRejected, readPromise
, Callback(..)
, withCallback
, AudioBufferCallback(..), noAudioBufferCallback
, BlobCallback(..), noBlobCallback
, DatabaseCallback(..), noDatabaseCallback
, IntersectionObserverCallback(..), noIntersectionObserverCallback
, MediaQueryListListener(..), noMediaQueryListListener
, MediaStreamTrackSourcesCallback(..), noMediaStreamTrackSourcesCallback
, NavigatorUserMediaErrorCallback(..), noNavigatorUserMediaErrorCallback
, NavigatorUserMediaSuccessCallback(..), noNavigatorUserMediaSuccessCallback
, NotificationPermissionCallback(..)
, NodeFilter(..), noNodeFilter
, PositionCallback(..), noPositionCallback
, PositionErrorCallback(..), noPositionErrorCallback
, PerformanceObserverCallback(..), noPerformanceObserverCallback
, RequestAnimationFrameCallback(..), noRequestAnimationFrameCallback
, RTCPeerConnectionErrorCallback(..), noRTCPeerConnectionErrorCallback
, RTCSessionDescriptionCallback(..), noRTCSessionDescriptionCallback
, RTCStatsCallback(..), noRTCStatsCallback
, SQLStatementCallback(..), noSQLStatementCallback
, SQLStatementErrorCallback(..), noSQLStatementErrorCallback
, SQLTransactionCallback(..), noSQLTransactionCallback
, SQLTransactionErrorCallback(..), noSQLTransactionErrorCallback
, StorageErrorCallback(..), noStorageErrorCallback
, StorageQuotaCallback(..), noStorageQuotaCallback
, StorageUsageCallback(..), noStorageUsageCallback
, StringCallback(..)
, VoidCallback(..), noVoidCallback
, DOMHighResTimeStamp, noDOMHighResTimeStamp
, PerformanceEntryList, noPerformanceEntryList
, Record(Record), unRecord
, Dictionary(Dictionary), unDictionary, IsDictionary, toDictionary, noDictionary
, MutationCallback(MutationCallback), unMutationCallback, IsMutationCallback, toMutationCallback, noMutationCallback
, Date(Date), unDate, IsDate, toDate, gTypeDate, noDate
, Array(Array), unArray, IsArray, toArray, gTypeArray, noArray
, ObjectArray(ObjectArray), unObjectArray, IsObjectArray, toObjectArray, noObjectArray
, ArrayBuffer(ArrayBuffer), unArrayBuffer, IsArrayBuffer, toArrayBuffer, gTypeArrayBuffer, noArrayBuffer
, ArrayBufferView(ArrayBufferView), unArrayBufferView, IsArrayBufferView, toArrayBufferView, noArrayBufferView
, Float32Array(Float32Array), unFloat32Array, IsFloat32Array, toFloat32Array, gTypeFloat32Array, noFloat32Array
, Float64Array(Float64Array), unFloat64Array, IsFloat64Array, toFloat64Array, gTypeFloat64Array, noFloat64Array
, Uint8Array(Uint8Array), unUint8Array, IsUint8Array, toUint8Array, gTypeUint8Array, noUint8Array
, Uint8ClampedArray(Uint8ClampedArray), unUint8ClampedArray, IsUint8ClampedArray, toUint8ClampedArray, gTypeUint8ClampedArray, noUint8ClampedArray
, Uint16Array(Uint16Array), unUint16Array, IsUint16Array, toUint16Array, gTypeUint16Array, noUint16Array
, Uint32Array(Uint32Array), unUint32Array, IsUint32Array, toUint32Array, gTypeUint32Array, noUint32Array
, Int8Array(Int8Array), unInt8Array, IsInt8Array, toInt8Array, gTypeInt8Array, noInt8Array
, Int16Array(Int16Array), unInt16Array, IsInt16Array, toInt16Array, gTypeInt16Array, noInt16Array
, Int32Array(Int32Array), unInt32Array, IsInt32Array, toInt32Array, gTypeInt32Array, noInt32Array
, SerializedScriptValue(SerializedScriptValue), unSerializedScriptValue, IsSerializedScriptValue, toSerializedScriptValue, noSerializedScriptValue
, Algorithm(Algorithm), unAlgorithm, IsAlgorithm, toAlgorithm, noAlgorithm
, CryptoOperationData(CryptoOperationData), unCryptoOperationData, IsCryptoOperationData, toCryptoOperationData, noCryptoOperationData
, GLenum(..), GLboolean(..), GLbitfield(..), GLbyte(..), GLshort(..), GLint(..), GLsizei(..)
, GLintptr(..), GLsizeiptr(..), GLubyte(..), GLushort(..), GLuint(..), GLfloat(..), GLclampf(..)
, GLint64, GLuint64
, noGLenum, noGLboolean, noGLbitfield, noGLbyte, noGLshort, noGLint, noGLsizei
, noGLintptr, noGLsizeiptr, noGLubyte, noGLushort, noGLuint, noGLfloat, noGLclampf
, noGLint64, noGLuint64
, HasCallStack
, AddEventListenerOptionsOrBool(AddEventListenerOptionsOrBool), unAddEventListenerOptionsOrBool, IsAddEventListenerOptionsOrBool, toAddEventListenerOptionsOrBool
, BinaryData(BinaryData), unBinaryData, IsBinaryData, toBinaryData
, BlobPart(BlobPart), unBlobPart, IsBlobPart
, BodyInit(BodyInit), unBodyInit, IsBodyInit
, BufferDataSource(BufferDataSource), unBufferDataSource, IsBufferDataSource, toBufferDataSource
, BufferSource(BufferSource), unBufferSource, IsBufferSource, toBufferSource
, CanvasImageSource(CanvasImageSource), unCanvasImageSource, IsCanvasImageSource, toCanvasImageSource
, CanvasStyle(CanvasStyle), unCanvasStyle, IsCanvasStyle
, CredentialBodyType(CredentialBodyType), unCredentialBodyType, IsCredentialBodyType, toCredentialBodyType
, CryptoKeyOrKeyPair(CryptoKeyOrKeyPair), unCryptoKeyOrKeyPair, IsCryptoKeyOrKeyPair, toCryptoKeyOrKeyPair
, EventListenerOptionsOrBool(EventListenerOptionsOrBool), unEventListenerOptionsOrBool, IsEventListenerOptionsOrBool, toEventListenerOptionsOrBool
, Float32List(Float32List), unFloat32List, IsFloat32List
, HTMLCollectionOrElement(HTMLCollectionOrElement), unHTMLCollectionOrElement, IsHTMLCollectionOrElement, toHTMLCollectionOrElement
, HTMLElementOrLong(HTMLElementOrLong), unHTMLElementOrLong, IsHTMLElementOrLong
, HTMLOptionElementOrGroup(HTMLOptionElementOrGroup), unHTMLOptionElementOrGroup, IsHTMLOptionElementOrGroup, toHTMLOptionElementOrGroup
, IDBCursorSource(IDBCursorSource), unIDBCursorSource, IsIDBCursorSource, toIDBCursorSource
, IDBKeyPath(IDBKeyPath), unIDBKeyPath, IsIDBKeyPath
, IDBRequestResult(IDBRequestResult), unIDBRequestResult, IsIDBRequestResult, toIDBRequestResult
, IDBRequestSource(IDBRequestSource), unIDBRequestSource, IsIDBRequestSource, toIDBRequestSource
, Int32List(Int32List), unInt32List, IsInt32List
, KeyData(KeyData), unKeyData, IsKeyData, toKeyData
, MediaProvider(MediaProvider), unMediaProvider, IsMediaProvider, toMediaProvider
, MediaStreamTrackOrKind(MediaStreamTrackOrKind), unMediaStreamTrackOrKind, IsMediaStreamTrackOrKind
, MessageEventSource(MessageEventSource), unMessageEventSource, IsMessageEventSource, toMessageEventSource
, NodeOrString(NodeOrString), unNodeOrString, IsNodeOrString
, RTCIceCandidateOrInit(RTCIceCandidateOrInit), unRTCIceCandidateOrInit, IsRTCIceCandidateOrInit, toRTCIceCandidateOrInit
, RadioNodeListOrElement(RadioNodeListOrElement), unRadioNodeListOrElement, IsRadioNodeListOrElement, toRadioNodeListOrElement
, RenderingContext(RenderingContext), unRenderingContext, IsRenderingContext, toRenderingContext
, SQLValue(SQLValue), unSQLValue, IsSQLValue
, StringOrArrayBuffer(StringOrArrayBuffer), unStringOrArrayBuffer, IsStringOrArrayBuffer
, StringOrBinaryData(StringOrBinaryData), unStringOrBinaryData, IsStringOrBinaryData
, StringOrStrings(StringOrStrings), unStringOrStrings, IsStringOrStrings
, TexImageSource(TexImageSource), unTexImageSource, IsTexImageSource, toTexImageSource
, Track(Track), unTrack, IsTrack, toTrack
, URLSearchParamsInit(URLSearchParamsInit), unURLSearchParamsInit, IsURLSearchParamsInit
, XMLHttpRequestBody(XMLHttpRequestBody), unXMLHttpRequestBody, IsXMLHttpRequestBody
, ANGLEInstancedArrays(ANGLEInstancedArrays), unANGLEInstancedArrays, noANGLEInstancedArrays, gTypeANGLEInstancedArrays
, AbstractWorker(AbstractWorker), unAbstractWorker, IsAbstractWorker, toAbstractWorker, noAbstractWorker, gTypeAbstractWorker
, Acceleration(Acceleration), unAcceleration, noAcceleration, gTypeAcceleration
, AddEventListenerOptions(AddEventListenerOptions), unAddEventListenerOptions, noAddEventListenerOptions, gTypeAddEventListenerOptions
, AesCbcCfbParams(AesCbcCfbParams), unAesCbcCfbParams, noAesCbcCfbParams, gTypeAesCbcCfbParams
, AesCtrParams(AesCtrParams), unAesCtrParams, noAesCtrParams, gTypeAesCtrParams
, AesGcmParams(AesGcmParams), unAesGcmParams, noAesGcmParams, gTypeAesGcmParams
, AesKeyParams(AesKeyParams), unAesKeyParams, noAesKeyParams, gTypeAesKeyParams
, AnalyserNode(AnalyserNode), unAnalyserNode, noAnalyserNode, gTypeAnalyserNode
, Animatable(Animatable), unAnimatable, IsAnimatable, toAnimatable, noAnimatable, gTypeAnimatable
, Animation(Animation), unAnimation, noAnimation, gTypeAnimation
, AnimationEffect(AnimationEffect), unAnimationEffect, IsAnimationEffect, toAnimationEffect, noAnimationEffect, gTypeAnimationEffect
, AnimationEvent(AnimationEvent), unAnimationEvent, noAnimationEvent, gTypeAnimationEvent
, AnimationEventInit(AnimationEventInit), unAnimationEventInit, noAnimationEventInit, gTypeAnimationEventInit
, AnimationTimeline(AnimationTimeline), unAnimationTimeline, IsAnimationTimeline, toAnimationTimeline, noAnimationTimeline, gTypeAnimationTimeline
, ApplePayError(ApplePayError), unApplePayError, noApplePayError, gTypeApplePayError
, ApplePayLineItem(ApplePayLineItem), unApplePayLineItem, noApplePayLineItem, gTypeApplePayLineItem
, ApplePayPayment(ApplePayPayment), unApplePayPayment, noApplePayPayment, gTypeApplePayPayment
, ApplePayPaymentAuthorizationResult(ApplePayPaymentAuthorizationResult), unApplePayPaymentAuthorizationResult, noApplePayPaymentAuthorizationResult, gTypeApplePayPaymentAuthorizationResult
, ApplePayPaymentAuthorizedEvent(ApplePayPaymentAuthorizedEvent), unApplePayPaymentAuthorizedEvent, noApplePayPaymentAuthorizedEvent, gTypeApplePayPaymentAuthorizedEvent
, ApplePayPaymentContact(ApplePayPaymentContact), unApplePayPaymentContact, noApplePayPaymentContact, gTypeApplePayPaymentContact
, ApplePayPaymentMethod(ApplePayPaymentMethod), unApplePayPaymentMethod, noApplePayPaymentMethod, gTypeApplePayPaymentMethod
, ApplePayPaymentMethodSelectedEvent(ApplePayPaymentMethodSelectedEvent), unApplePayPaymentMethodSelectedEvent, noApplePayPaymentMethodSelectedEvent, gTypeApplePayPaymentMethodSelectedEvent
, ApplePayPaymentMethodUpdate(ApplePayPaymentMethodUpdate), unApplePayPaymentMethodUpdate, noApplePayPaymentMethodUpdate, gTypeApplePayPaymentMethodUpdate
, ApplePayPaymentPass(ApplePayPaymentPass), unApplePayPaymentPass, noApplePayPaymentPass, gTypeApplePayPaymentPass
, ApplePayPaymentRequest(ApplePayPaymentRequest), unApplePayPaymentRequest, noApplePayPaymentRequest, gTypeApplePayPaymentRequest
, ApplePayPaymentToken(ApplePayPaymentToken), unApplePayPaymentToken, noApplePayPaymentToken, gTypeApplePayPaymentToken
, ApplePaySession(ApplePaySession), unApplePaySession, noApplePaySession, gTypeApplePaySession
, ApplePayShippingContactSelectedEvent(ApplePayShippingContactSelectedEvent), unApplePayShippingContactSelectedEvent, noApplePayShippingContactSelectedEvent, gTypeApplePayShippingContactSelectedEvent
, ApplePayShippingContactUpdate(ApplePayShippingContactUpdate), unApplePayShippingContactUpdate, noApplePayShippingContactUpdate, gTypeApplePayShippingContactUpdate
, ApplePayShippingMethod(ApplePayShippingMethod), unApplePayShippingMethod, noApplePayShippingMethod, gTypeApplePayShippingMethod
, ApplePayShippingMethodSelectedEvent(ApplePayShippingMethodSelectedEvent), unApplePayShippingMethodSelectedEvent, noApplePayShippingMethodSelectedEvent, gTypeApplePayShippingMethodSelectedEvent
, ApplePayShippingMethodUpdate(ApplePayShippingMethodUpdate), unApplePayShippingMethodUpdate, noApplePayShippingMethodUpdate, gTypeApplePayShippingMethodUpdate
, ApplePayValidateMerchantEvent(ApplePayValidateMerchantEvent), unApplePayValidateMerchantEvent, noApplePayValidateMerchantEvent, gTypeApplePayValidateMerchantEvent
, ApplicationCache(ApplicationCache), unApplicationCache, noApplicationCache, gTypeApplicationCache
, AssignedNodesOptions(AssignedNodesOptions), unAssignedNodesOptions, noAssignedNodesOptions, gTypeAssignedNodesOptions
, Attr(Attr), unAttr, noAttr, gTypeAttr
, AudioBuffer(AudioBuffer), unAudioBuffer, noAudioBuffer, gTypeAudioBuffer
, AudioBufferSourceNode(AudioBufferSourceNode), unAudioBufferSourceNode, noAudioBufferSourceNode, gTypeAudioBufferSourceNode
, AudioContext(AudioContext), unAudioContext, IsAudioContext, toAudioContext, noAudioContext, gTypeAudioContext
, AudioDestinationNode(AudioDestinationNode), unAudioDestinationNode, noAudioDestinationNode, gTypeAudioDestinationNode
, AudioListener(AudioListener), unAudioListener, noAudioListener, gTypeAudioListener
, AudioNode(AudioNode), unAudioNode, IsAudioNode, toAudioNode, noAudioNode, gTypeAudioNode
, AudioParam(AudioParam), unAudioParam, noAudioParam, gTypeAudioParam
, AudioProcessingEvent(AudioProcessingEvent), unAudioProcessingEvent, noAudioProcessingEvent, gTypeAudioProcessingEvent
, AudioTrack(AudioTrack), unAudioTrack, noAudioTrack, gTypeAudioTrack
, AudioTrackList(AudioTrackList), unAudioTrackList, noAudioTrackList, gTypeAudioTrackList
, AutocompleteErrorEvent(AutocompleteErrorEvent), unAutocompleteErrorEvent, noAutocompleteErrorEvent, gTypeAutocompleteErrorEvent
, AutocompleteErrorEventInit(AutocompleteErrorEventInit), unAutocompleteErrorEventInit, noAutocompleteErrorEventInit, gTypeAutocompleteErrorEventInit
, BarProp(BarProp), unBarProp, noBarProp, gTypeBarProp
, BasicCredential(BasicCredential), unBasicCredential, IsBasicCredential, toBasicCredential, noBasicCredential, gTypeBasicCredential
, BeforeLoadEvent(BeforeLoadEvent), unBeforeLoadEvent, noBeforeLoadEvent, gTypeBeforeLoadEvent
, BeforeLoadEventInit(BeforeLoadEventInit), unBeforeLoadEventInit, noBeforeLoadEventInit, gTypeBeforeLoadEventInit
, BeforeUnloadEvent(BeforeUnloadEvent), unBeforeUnloadEvent, noBeforeUnloadEvent, gTypeBeforeUnloadEvent
, BiquadFilterNode(BiquadFilterNode), unBiquadFilterNode, noBiquadFilterNode, gTypeBiquadFilterNode
, Blob(Blob), unBlob, IsBlob, toBlob, noBlob, gTypeBlob
, BlobPropertyBag(BlobPropertyBag), unBlobPropertyBag, IsBlobPropertyBag, toBlobPropertyBag, noBlobPropertyBag, gTypeBlobPropertyBag
, Body(Body), unBody, IsBody, toBody, noBody, gTypeBody
, ByteLengthQueuingStrategy(ByteLengthQueuingStrategy), unByteLengthQueuingStrategy, noByteLengthQueuingStrategy, gTypeByteLengthQueuingStrategy
, CDATASection(CDATASection), unCDATASection, noCDATASection, gTypeCDATASection
, CSS(CSS), unCSS, noCSS, gTypeCSS
, CSSFontFaceLoadEvent(CSSFontFaceLoadEvent), unCSSFontFaceLoadEvent, noCSSFontFaceLoadEvent, gTypeCSSFontFaceLoadEvent
, CSSFontFaceLoadEventInit(CSSFontFaceLoadEventInit), unCSSFontFaceLoadEventInit, noCSSFontFaceLoadEventInit, gTypeCSSFontFaceLoadEventInit
, CSSFontFaceRule(CSSFontFaceRule), unCSSFontFaceRule, noCSSFontFaceRule, gTypeCSSFontFaceRule
, CSSImportRule(CSSImportRule), unCSSImportRule, noCSSImportRule, gTypeCSSImportRule
, CSSKeyframeRule(CSSKeyframeRule), unCSSKeyframeRule, noCSSKeyframeRule, gTypeCSSKeyframeRule
, CSSKeyframesRule(CSSKeyframesRule), unCSSKeyframesRule, noCSSKeyframesRule, gTypeCSSKeyframesRule
, CSSMediaRule(CSSMediaRule), unCSSMediaRule, noCSSMediaRule, gTypeCSSMediaRule
, CSSNamespaceRule(CSSNamespaceRule), unCSSNamespaceRule, noCSSNamespaceRule, gTypeCSSNamespaceRule
, CSSPageRule(CSSPageRule), unCSSPageRule, noCSSPageRule, gTypeCSSPageRule
, CSSPrimitiveValue(CSSPrimitiveValue), unCSSPrimitiveValue, noCSSPrimitiveValue, gTypeCSSPrimitiveValue
, CSSRule(CSSRule), unCSSRule, IsCSSRule, toCSSRule, noCSSRule, gTypeCSSRule
, CSSRuleList(CSSRuleList), unCSSRuleList, noCSSRuleList, gTypeCSSRuleList
, CSSStyleDeclaration(CSSStyleDeclaration), unCSSStyleDeclaration, noCSSStyleDeclaration, gTypeCSSStyleDeclaration
, CSSStyleRule(CSSStyleRule), unCSSStyleRule, noCSSStyleRule, gTypeCSSStyleRule
, CSSStyleSheet(CSSStyleSheet), unCSSStyleSheet, noCSSStyleSheet, gTypeCSSStyleSheet
, CSSSupportsRule(CSSSupportsRule), unCSSSupportsRule, noCSSSupportsRule, gTypeCSSSupportsRule
, CSSUnknownRule(CSSUnknownRule), unCSSUnknownRule, noCSSUnknownRule, gTypeCSSUnknownRule
, CSSValue(CSSValue), unCSSValue, IsCSSValue, toCSSValue, noCSSValue, gTypeCSSValue
, CSSValueList(CSSValueList), unCSSValueList, noCSSValueList, gTypeCSSValueList
, CanvasCaptureMediaStreamTrack(CanvasCaptureMediaStreamTrack), unCanvasCaptureMediaStreamTrack, noCanvasCaptureMediaStreamTrack, gTypeCanvasCaptureMediaStreamTrack
, CanvasGradient(CanvasGradient), unCanvasGradient, noCanvasGradient, gTypeCanvasGradient
, CanvasPath(CanvasPath), unCanvasPath, IsCanvasPath, toCanvasPath, noCanvasPath, gTypeCanvasPath
, CanvasPattern(CanvasPattern), unCanvasPattern, noCanvasPattern, gTypeCanvasPattern
, CanvasProxy(CanvasProxy), unCanvasProxy, noCanvasProxy, gTypeCanvasProxy
, CanvasRenderingContext2D(CanvasRenderingContext2D), unCanvasRenderingContext2D, noCanvasRenderingContext2D, gTypeCanvasRenderingContext2D
, ChannelMergerNode(ChannelMergerNode), unChannelMergerNode, noChannelMergerNode, gTypeChannelMergerNode
, ChannelSplitterNode(ChannelSplitterNode), unChannelSplitterNode, noChannelSplitterNode, gTypeChannelSplitterNode
, CharacterData(CharacterData), unCharacterData, IsCharacterData, toCharacterData, noCharacterData, gTypeCharacterData
, ChildNode(ChildNode), unChildNode, IsChildNode, toChildNode, noChildNode, gTypeChildNode
, ClipboardEvent(ClipboardEvent), unClipboardEvent, noClipboardEvent, gTypeClipboardEvent
, ClipboardEventInit(ClipboardEventInit), unClipboardEventInit, noClipboardEventInit, gTypeClipboardEventInit
, CloseEvent(CloseEvent), unCloseEvent, noCloseEvent, gTypeCloseEvent
, CloseEventInit(CloseEventInit), unCloseEventInit, noCloseEventInit, gTypeCloseEventInit
, CommandLineAPIHost(CommandLineAPIHost), unCommandLineAPIHost, noCommandLineAPIHost, gTypeCommandLineAPIHost
, Comment(Comment), unComment, noComment, gTypeComment
, CompositionEvent(CompositionEvent), unCompositionEvent, noCompositionEvent, gTypeCompositionEvent
, CompositionEventInit(CompositionEventInit), unCompositionEventInit, noCompositionEventInit, gTypeCompositionEventInit
, ConstrainBooleanParameters(ConstrainBooleanParameters), unConstrainBooleanParameters, noConstrainBooleanParameters, gTypeConstrainBooleanParameters
, ConstrainDOMStringParameters(ConstrainDOMStringParameters), unConstrainDOMStringParameters, noConstrainDOMStringParameters, gTypeConstrainDOMStringParameters
, ConstrainDoubleRange(ConstrainDoubleRange), unConstrainDoubleRange, noConstrainDoubleRange, gTypeConstrainDoubleRange
, ConstrainLongRange(ConstrainLongRange), unConstrainLongRange, noConstrainLongRange, gTypeConstrainLongRange
, ConvolverNode(ConvolverNode), unConvolverNode, noConvolverNode, gTypeConvolverNode
, Coordinates(Coordinates), unCoordinates, noCoordinates, gTypeCoordinates
, CountQueuingStrategy(CountQueuingStrategy), unCountQueuingStrategy, noCountQueuingStrategy, gTypeCountQueuingStrategy
, Counter(Counter), unCounter, noCounter, gTypeCounter
, CredentialData(CredentialData), unCredentialData, IsCredentialData, toCredentialData, noCredentialData, gTypeCredentialData
, Crypto(Crypto), unCrypto, noCrypto, gTypeCrypto
, CryptoAlgorithmParameters(CryptoAlgorithmParameters), unCryptoAlgorithmParameters, IsCryptoAlgorithmParameters, toCryptoAlgorithmParameters, noCryptoAlgorithmParameters, gTypeCryptoAlgorithmParameters
, CryptoKey(CryptoKey), unCryptoKey, noCryptoKey, gTypeCryptoKey
, CryptoKeyPair(CryptoKeyPair), unCryptoKeyPair, noCryptoKeyPair, gTypeCryptoKeyPair
, CustomElementRegistry(CustomElementRegistry), unCustomElementRegistry, noCustomElementRegistry, gTypeCustomElementRegistry
, CustomEvent(CustomEvent), unCustomEvent, noCustomEvent, gTypeCustomEvent
, CustomEventInit(CustomEventInit), unCustomEventInit, noCustomEventInit, gTypeCustomEventInit
, DOMError(DOMError), unDOMError, IsDOMError, toDOMError, noDOMError, gTypeDOMError
, DOMException(DOMException), unDOMException, noDOMException, gTypeDOMException
, DOMImplementation(DOMImplementation), unDOMImplementation, noDOMImplementation, gTypeDOMImplementation
, DOMNamedFlowCollection(DOMNamedFlowCollection), unDOMNamedFlowCollection, noDOMNamedFlowCollection, gTypeDOMNamedFlowCollection
, DOMParser(DOMParser), unDOMParser, noDOMParser, gTypeDOMParser
, DOMPoint(DOMPoint), unDOMPoint, noDOMPoint, gTypeDOMPoint
, DOMPointInit(DOMPointInit), unDOMPointInit, noDOMPointInit, gTypeDOMPointInit
, DOMPointReadOnly(DOMPointReadOnly), unDOMPointReadOnly, IsDOMPointReadOnly, toDOMPointReadOnly, noDOMPointReadOnly, gTypeDOMPointReadOnly
, DOMRect(DOMRect), unDOMRect, noDOMRect, gTypeDOMRect
, DOMRectInit(DOMRectInit), unDOMRectInit, noDOMRectInit, gTypeDOMRectInit
, DOMRectReadOnly(DOMRectReadOnly), unDOMRectReadOnly, IsDOMRectReadOnly, toDOMRectReadOnly, noDOMRectReadOnly, gTypeDOMRectReadOnly
, DOMStringList(DOMStringList), unDOMStringList, noDOMStringList, gTypeDOMStringList
, DOMStringMap(DOMStringMap), unDOMStringMap, noDOMStringMap, gTypeDOMStringMap
, DOMTokenList(DOMTokenList), unDOMTokenList, noDOMTokenList, gTypeDOMTokenList
, DataCue(DataCue), unDataCue, noDataCue, gTypeDataCue
, DataTransfer(DataTransfer), unDataTransfer, noDataTransfer, gTypeDataTransfer
, DataTransferItem(DataTransferItem), unDataTransferItem, noDataTransferItem, gTypeDataTransferItem
, DataTransferItemList(DataTransferItemList), unDataTransferItemList, noDataTransferItemList, gTypeDataTransferItemList
, Database(Database), unDatabase, noDatabase, gTypeDatabase
, DedicatedWorkerGlobalScope(DedicatedWorkerGlobalScope), unDedicatedWorkerGlobalScope, noDedicatedWorkerGlobalScope, gTypeDedicatedWorkerGlobalScope
, DelayNode(DelayNode), unDelayNode, noDelayNode, gTypeDelayNode
, DeviceMotionEvent(DeviceMotionEvent), unDeviceMotionEvent, noDeviceMotionEvent, gTypeDeviceMotionEvent
, DeviceOrientationEvent(DeviceOrientationEvent), unDeviceOrientationEvent, noDeviceOrientationEvent, gTypeDeviceOrientationEvent
, DeviceProximityEvent(DeviceProximityEvent), unDeviceProximityEvent, noDeviceProximityEvent, gTypeDeviceProximityEvent
, DeviceProximityEventInit(DeviceProximityEventInit), unDeviceProximityEventInit, noDeviceProximityEventInit, gTypeDeviceProximityEventInit
, Document(Document), unDocument, IsDocument, toDocument, noDocument, gTypeDocument
, DocumentAndElementEventHandlers(DocumentAndElementEventHandlers), unDocumentAndElementEventHandlers, IsDocumentAndElementEventHandlers, toDocumentAndElementEventHandlers, noDocumentAndElementEventHandlers, gTypeDocumentAndElementEventHandlers
, DocumentFragment(DocumentFragment), unDocumentFragment, IsDocumentFragment, toDocumentFragment, noDocumentFragment, gTypeDocumentFragment
, DocumentOrShadowRoot(DocumentOrShadowRoot), unDocumentOrShadowRoot, IsDocumentOrShadowRoot, toDocumentOrShadowRoot, noDocumentOrShadowRoot, gTypeDocumentOrShadowRoot
, DocumentTimeline(DocumentTimeline), unDocumentTimeline, noDocumentTimeline, gTypeDocumentTimeline
, DocumentType(DocumentType), unDocumentType, noDocumentType, gTypeDocumentType
, DoubleRange(DoubleRange), unDoubleRange, IsDoubleRange, toDoubleRange, noDoubleRange, gTypeDoubleRange
, DynamicsCompressorNode(DynamicsCompressorNode), unDynamicsCompressorNode, noDynamicsCompressorNode, gTypeDynamicsCompressorNode
, EXTBlendMinMax(EXTBlendMinMax), unEXTBlendMinMax, noEXTBlendMinMax, gTypeEXTBlendMinMax
, EXTFragDepth(EXTFragDepth), unEXTFragDepth, noEXTFragDepth, gTypeEXTFragDepth
, EXTShaderTextureLOD(EXTShaderTextureLOD), unEXTShaderTextureLOD, noEXTShaderTextureLOD, gTypeEXTShaderTextureLOD
, EXTTextureFilterAnisotropic(EXTTextureFilterAnisotropic), unEXTTextureFilterAnisotropic, noEXTTextureFilterAnisotropic, gTypeEXTTextureFilterAnisotropic
, EXTsRGB(EXTsRGB), unEXTsRGB, noEXTsRGB, gTypeEXTsRGB
, EcKeyParams(EcKeyParams), unEcKeyParams, noEcKeyParams, gTypeEcKeyParams
, EcdhKeyDeriveParams(EcdhKeyDeriveParams), unEcdhKeyDeriveParams, noEcdhKeyDeriveParams, gTypeEcdhKeyDeriveParams
, EcdsaParams(EcdsaParams), unEcdsaParams, noEcdsaParams, gTypeEcdsaParams
, Element(Element), unElement, IsElement, toElement, noElement, gTypeElement
, ElementCSSInlineStyle(ElementCSSInlineStyle), unElementCSSInlineStyle, IsElementCSSInlineStyle, toElementCSSInlineStyle, noElementCSSInlineStyle, gTypeElementCSSInlineStyle
, ErrorEvent(ErrorEvent), unErrorEvent, noErrorEvent, gTypeErrorEvent
, ErrorEventInit(ErrorEventInit), unErrorEventInit, noErrorEventInit, gTypeErrorEventInit
, Event(Event), unEvent, IsEvent, toEvent, noEvent, gTypeEvent
, EventInit(EventInit), unEventInit, IsEventInit, toEventInit, noEventInit, gTypeEventInit
, EventListener(EventListener), unEventListener, noEventListener, gTypeEventListener
, EventListenerOptions(EventListenerOptions), unEventListenerOptions, IsEventListenerOptions, toEventListenerOptions, noEventListenerOptions, gTypeEventListenerOptions
, EventModifierInit(EventModifierInit), unEventModifierInit, IsEventModifierInit, toEventModifierInit, noEventModifierInit, gTypeEventModifierInit
, EventSource(EventSource), unEventSource, noEventSource, gTypeEventSource
, EventSourceInit(EventSourceInit), unEventSourceInit, noEventSourceInit, gTypeEventSourceInit
, EventTarget(EventTarget), unEventTarget, IsEventTarget, toEventTarget, noEventTarget, gTypeEventTarget
, File(File), unFile, noFile, gTypeFile
, FileError(FileError), unFileError, noFileError, gTypeFileError
, FileException(FileException), unFileException, noFileException, gTypeFileException
, FileList(FileList), unFileList, noFileList, gTypeFileList
, FilePropertyBag(FilePropertyBag), unFilePropertyBag, noFilePropertyBag, gTypeFilePropertyBag
, FileReader(FileReader), unFileReader, noFileReader, gTypeFileReader
, FileReaderSync(FileReaderSync), unFileReaderSync, noFileReaderSync, gTypeFileReaderSync
, FocusEvent(FocusEvent), unFocusEvent, noFocusEvent, gTypeFocusEvent
, FocusEventInit(FocusEventInit), unFocusEventInit, noFocusEventInit, gTypeFocusEventInit
, FontFace(FontFace), unFontFace, noFontFace, gTypeFontFace
, FontFaceDescriptors(FontFaceDescriptors), unFontFaceDescriptors, noFontFaceDescriptors, gTypeFontFaceDescriptors
, FontFaceSet(FontFaceSet), unFontFaceSet, noFontFaceSet, gTypeFontFaceSet
, FormData(FormData), unFormData, noFormData, gTypeFormData
, GainNode(GainNode), unGainNode, noGainNode, gTypeGainNode
, Gamepad(Gamepad), unGamepad, noGamepad, gTypeGamepad
, GamepadButton(GamepadButton), unGamepadButton, noGamepadButton, gTypeGamepadButton
, GamepadEvent(GamepadEvent), unGamepadEvent, noGamepadEvent, gTypeGamepadEvent
, GamepadEventInit(GamepadEventInit), unGamepadEventInit, noGamepadEventInit, gTypeGamepadEventInit
, Geolocation(Geolocation), unGeolocation, noGeolocation, gTypeGeolocation
, Geoposition(Geoposition), unGeoposition, noGeoposition, gTypeGeoposition
, GetRootNodeOptions(GetRootNodeOptions), unGetRootNodeOptions, noGetRootNodeOptions, gTypeGetRootNodeOptions
, GlobalCrypto(GlobalCrypto), unGlobalCrypto, IsGlobalCrypto, toGlobalCrypto, noGlobalCrypto, gTypeGlobalCrypto
, GlobalEventHandlers(GlobalEventHandlers), unGlobalEventHandlers, IsGlobalEventHandlers, toGlobalEventHandlers, noGlobalEventHandlers, gTypeGlobalEventHandlers
, GlobalPerformance(GlobalPerformance), unGlobalPerformance, IsGlobalPerformance, toGlobalPerformance, noGlobalPerformance, gTypeGlobalPerformance
, HTMLAllCollection(HTMLAllCollection), unHTMLAllCollection, noHTMLAllCollection, gTypeHTMLAllCollection
, HTMLAnchorElement(HTMLAnchorElement), unHTMLAnchorElement, noHTMLAnchorElement, gTypeHTMLAnchorElement
, HTMLAppletElement(HTMLAppletElement), unHTMLAppletElement, noHTMLAppletElement, gTypeHTMLAppletElement
, HTMLAreaElement(HTMLAreaElement), unHTMLAreaElement, noHTMLAreaElement, gTypeHTMLAreaElement
, HTMLAttachmentElement(HTMLAttachmentElement), unHTMLAttachmentElement, noHTMLAttachmentElement, gTypeHTMLAttachmentElement
, HTMLAudioElement(HTMLAudioElement), unHTMLAudioElement, noHTMLAudioElement, gTypeHTMLAudioElement
, HTMLBRElement(HTMLBRElement), unHTMLBRElement, noHTMLBRElement, gTypeHTMLBRElement
, HTMLBaseElement(HTMLBaseElement), unHTMLBaseElement, noHTMLBaseElement, gTypeHTMLBaseElement
, HTMLBodyElement(HTMLBodyElement), unHTMLBodyElement, noHTMLBodyElement, gTypeHTMLBodyElement
, HTMLButtonElement(HTMLButtonElement), unHTMLButtonElement, noHTMLButtonElement, gTypeHTMLButtonElement
, HTMLCanvasElement(HTMLCanvasElement), unHTMLCanvasElement, noHTMLCanvasElement, gTypeHTMLCanvasElement
, HTMLCollection(HTMLCollection), unHTMLCollection, IsHTMLCollection, toHTMLCollection, noHTMLCollection, gTypeHTMLCollection
, HTMLDListElement(HTMLDListElement), unHTMLDListElement, noHTMLDListElement, gTypeHTMLDListElement
, HTMLDataElement(HTMLDataElement), unHTMLDataElement, noHTMLDataElement, gTypeHTMLDataElement
, HTMLDataListElement(HTMLDataListElement), unHTMLDataListElement, noHTMLDataListElement, gTypeHTMLDataListElement
, HTMLDetailsElement(HTMLDetailsElement), unHTMLDetailsElement, noHTMLDetailsElement, gTypeHTMLDetailsElement
, HTMLDirectoryElement(HTMLDirectoryElement), unHTMLDirectoryElement, noHTMLDirectoryElement, gTypeHTMLDirectoryElement
, HTMLDivElement(HTMLDivElement), unHTMLDivElement, noHTMLDivElement, gTypeHTMLDivElement
, HTMLDocument(HTMLDocument), unHTMLDocument, noHTMLDocument, gTypeHTMLDocument
, HTMLElement(HTMLElement), unHTMLElement, IsHTMLElement, toHTMLElement, noHTMLElement, gTypeHTMLElement
, HTMLEmbedElement(HTMLEmbedElement), unHTMLEmbedElement, noHTMLEmbedElement, gTypeHTMLEmbedElement
, HTMLFieldSetElement(HTMLFieldSetElement), unHTMLFieldSetElement, noHTMLFieldSetElement, gTypeHTMLFieldSetElement
, HTMLFontElement(HTMLFontElement), unHTMLFontElement, noHTMLFontElement, gTypeHTMLFontElement
, HTMLFormControlsCollection(HTMLFormControlsCollection), unHTMLFormControlsCollection, noHTMLFormControlsCollection, gTypeHTMLFormControlsCollection
, HTMLFormElement(HTMLFormElement), unHTMLFormElement, noHTMLFormElement, gTypeHTMLFormElement
, HTMLFrameElement(HTMLFrameElement), unHTMLFrameElement, noHTMLFrameElement, gTypeHTMLFrameElement
, HTMLFrameSetElement(HTMLFrameSetElement), unHTMLFrameSetElement, noHTMLFrameSetElement, gTypeHTMLFrameSetElement
, HTMLHRElement(HTMLHRElement), unHTMLHRElement, noHTMLHRElement, gTypeHTMLHRElement
, HTMLHeadElement(HTMLHeadElement), unHTMLHeadElement, noHTMLHeadElement, gTypeHTMLHeadElement
, HTMLHeadingElement(HTMLHeadingElement), unHTMLHeadingElement, noHTMLHeadingElement, gTypeHTMLHeadingElement
, HTMLHtmlElement(HTMLHtmlElement), unHTMLHtmlElement, noHTMLHtmlElement, gTypeHTMLHtmlElement
, HTMLHyperlinkElementUtils(HTMLHyperlinkElementUtils), unHTMLHyperlinkElementUtils, IsHTMLHyperlinkElementUtils, toHTMLHyperlinkElementUtils, noHTMLHyperlinkElementUtils, gTypeHTMLHyperlinkElementUtils
, HTMLIFrameElement(HTMLIFrameElement), unHTMLIFrameElement, noHTMLIFrameElement, gTypeHTMLIFrameElement
, HTMLImageElement(HTMLImageElement), unHTMLImageElement, noHTMLImageElement, gTypeHTMLImageElement
, HTMLInputElement(HTMLInputElement), unHTMLInputElement, noHTMLInputElement, gTypeHTMLInputElement
, HTMLKeygenElement(HTMLKeygenElement), unHTMLKeygenElement, noHTMLKeygenElement, gTypeHTMLKeygenElement
, HTMLLIElement(HTMLLIElement), unHTMLLIElement, noHTMLLIElement, gTypeHTMLLIElement
, HTMLLabelElement(HTMLLabelElement), unHTMLLabelElement, noHTMLLabelElement, gTypeHTMLLabelElement
, HTMLLegendElement(HTMLLegendElement), unHTMLLegendElement, noHTMLLegendElement, gTypeHTMLLegendElement
, HTMLLinkElement(HTMLLinkElement), unHTMLLinkElement, noHTMLLinkElement, gTypeHTMLLinkElement
, HTMLMapElement(HTMLMapElement), unHTMLMapElement, noHTMLMapElement, gTypeHTMLMapElement
, HTMLMarqueeElement(HTMLMarqueeElement), unHTMLMarqueeElement, noHTMLMarqueeElement, gTypeHTMLMarqueeElement
, HTMLMediaElement(HTMLMediaElement), unHTMLMediaElement, IsHTMLMediaElement, toHTMLMediaElement, noHTMLMediaElement, gTypeHTMLMediaElement
, HTMLMenuElement(HTMLMenuElement), unHTMLMenuElement, noHTMLMenuElement, gTypeHTMLMenuElement
, HTMLMetaElement(HTMLMetaElement), unHTMLMetaElement, noHTMLMetaElement, gTypeHTMLMetaElement
, HTMLMeterElement(HTMLMeterElement), unHTMLMeterElement, noHTMLMeterElement, gTypeHTMLMeterElement
, HTMLModElement(HTMLModElement), unHTMLModElement, noHTMLModElement, gTypeHTMLModElement
, HTMLOListElement(HTMLOListElement), unHTMLOListElement, noHTMLOListElement, gTypeHTMLOListElement
, HTMLObjectElement(HTMLObjectElement), unHTMLObjectElement, noHTMLObjectElement, gTypeHTMLObjectElement
, HTMLOptGroupElement(HTMLOptGroupElement), unHTMLOptGroupElement, noHTMLOptGroupElement, gTypeHTMLOptGroupElement
, HTMLOptionElement(HTMLOptionElement), unHTMLOptionElement, noHTMLOptionElement, gTypeHTMLOptionElement
, HTMLOptionsCollection(HTMLOptionsCollection), unHTMLOptionsCollection, noHTMLOptionsCollection, gTypeHTMLOptionsCollection
, HTMLOutputElement(HTMLOutputElement), unHTMLOutputElement, noHTMLOutputElement, gTypeHTMLOutputElement
, HTMLParagraphElement(HTMLParagraphElement), unHTMLParagraphElement, noHTMLParagraphElement, gTypeHTMLParagraphElement
, HTMLParamElement(HTMLParamElement), unHTMLParamElement, noHTMLParamElement, gTypeHTMLParamElement
, HTMLPictureElement(HTMLPictureElement), unHTMLPictureElement, noHTMLPictureElement, gTypeHTMLPictureElement
, HTMLPreElement(HTMLPreElement), unHTMLPreElement, noHTMLPreElement, gTypeHTMLPreElement
, HTMLProgressElement(HTMLProgressElement), unHTMLProgressElement, noHTMLProgressElement, gTypeHTMLProgressElement
, HTMLQuoteElement(HTMLQuoteElement), unHTMLQuoteElement, noHTMLQuoteElement, gTypeHTMLQuoteElement
, HTMLScriptElement(HTMLScriptElement), unHTMLScriptElement, noHTMLScriptElement, gTypeHTMLScriptElement
, HTMLSelectElement(HTMLSelectElement), unHTMLSelectElement, noHTMLSelectElement, gTypeHTMLSelectElement
, HTMLSlotElement(HTMLSlotElement), unHTMLSlotElement, noHTMLSlotElement, gTypeHTMLSlotElement
, HTMLSourceElement(HTMLSourceElement), unHTMLSourceElement, noHTMLSourceElement, gTypeHTMLSourceElement
, HTMLSpanElement(HTMLSpanElement), unHTMLSpanElement, noHTMLSpanElement, gTypeHTMLSpanElement
, HTMLStyleElement(HTMLStyleElement), unHTMLStyleElement, noHTMLStyleElement, gTypeHTMLStyleElement
, HTMLTableCaptionElement(HTMLTableCaptionElement), unHTMLTableCaptionElement, noHTMLTableCaptionElement, gTypeHTMLTableCaptionElement
, HTMLTableCellElement(HTMLTableCellElement), unHTMLTableCellElement, noHTMLTableCellElement, gTypeHTMLTableCellElement
, HTMLTableColElement(HTMLTableColElement), unHTMLTableColElement, noHTMLTableColElement, gTypeHTMLTableColElement
, HTMLTableElement(HTMLTableElement), unHTMLTableElement, noHTMLTableElement, gTypeHTMLTableElement
, HTMLTableRowElement(HTMLTableRowElement), unHTMLTableRowElement, noHTMLTableRowElement, gTypeHTMLTableRowElement
, HTMLTableSectionElement(HTMLTableSectionElement), unHTMLTableSectionElement, noHTMLTableSectionElement, gTypeHTMLTableSectionElement
, HTMLTemplateElement(HTMLTemplateElement), unHTMLTemplateElement, noHTMLTemplateElement, gTypeHTMLTemplateElement
, HTMLTextAreaElement(HTMLTextAreaElement), unHTMLTextAreaElement, noHTMLTextAreaElement, gTypeHTMLTextAreaElement
, HTMLTimeElement(HTMLTimeElement), unHTMLTimeElement, noHTMLTimeElement, gTypeHTMLTimeElement
, HTMLTitleElement(HTMLTitleElement), unHTMLTitleElement, noHTMLTitleElement, gTypeHTMLTitleElement
, HTMLTrackElement(HTMLTrackElement), unHTMLTrackElement, noHTMLTrackElement, gTypeHTMLTrackElement
, HTMLUListElement(HTMLUListElement), unHTMLUListElement, noHTMLUListElement, gTypeHTMLUListElement
, HTMLUnknownElement(HTMLUnknownElement), unHTMLUnknownElement, noHTMLUnknownElement, gTypeHTMLUnknownElement
, HTMLVideoElement(HTMLVideoElement), unHTMLVideoElement, noHTMLVideoElement, gTypeHTMLVideoElement
, HashChangeEvent(HashChangeEvent), unHashChangeEvent, noHashChangeEvent, gTypeHashChangeEvent
, HashChangeEventInit(HashChangeEventInit), unHashChangeEventInit, noHashChangeEventInit, gTypeHashChangeEventInit
, Headers(Headers), unHeaders, noHeaders, gTypeHeaders
, History(History), unHistory, noHistory, gTypeHistory
, HkdfParams(HkdfParams), unHkdfParams, noHkdfParams, gTypeHkdfParams
, HmacKeyParams(HmacKeyParams), unHmacKeyParams, noHmacKeyParams, gTypeHmacKeyParams
, IDBCursor(IDBCursor), unIDBCursor, IsIDBCursor, toIDBCursor, noIDBCursor, gTypeIDBCursor
, IDBCursorWithValue(IDBCursorWithValue), unIDBCursorWithValue, noIDBCursorWithValue, gTypeIDBCursorWithValue
, IDBDatabase(IDBDatabase), unIDBDatabase, noIDBDatabase, gTypeIDBDatabase
, IDBFactory(IDBFactory), unIDBFactory, noIDBFactory, gTypeIDBFactory
, IDBIndex(IDBIndex), unIDBIndex, noIDBIndex, gTypeIDBIndex
, IDBIndexParameters(IDBIndexParameters), unIDBIndexParameters, noIDBIndexParameters, gTypeIDBIndexParameters
, IDBKeyRange(IDBKeyRange), unIDBKeyRange, noIDBKeyRange, gTypeIDBKeyRange
, IDBObjectStore(IDBObjectStore), unIDBObjectStore, noIDBObjectStore, gTypeIDBObjectStore
, IDBObjectStoreParameters(IDBObjectStoreParameters), unIDBObjectStoreParameters, noIDBObjectStoreParameters, gTypeIDBObjectStoreParameters
, IDBOpenDBRequest(IDBOpenDBRequest), unIDBOpenDBRequest, noIDBOpenDBRequest, gTypeIDBOpenDBRequest
, IDBRequest(IDBRequest), unIDBRequest, IsIDBRequest, toIDBRequest, noIDBRequest, gTypeIDBRequest
, IDBTransaction(IDBTransaction), unIDBTransaction, noIDBTransaction, gTypeIDBTransaction
, IDBVersionChangeEvent(IDBVersionChangeEvent), unIDBVersionChangeEvent, noIDBVersionChangeEvent, gTypeIDBVersionChangeEvent
, IDBVersionChangeEventInit(IDBVersionChangeEventInit), unIDBVersionChangeEventInit, noIDBVersionChangeEventInit, gTypeIDBVersionChangeEventInit
, ImageData(ImageData), unImageData, noImageData, gTypeImageData
, InputEvent(InputEvent), unInputEvent, noInputEvent, gTypeInputEvent
, InputEventInit(InputEventInit), unInputEventInit, noInputEventInit, gTypeInputEventInit
, InspectorFrontendHost(InspectorFrontendHost), unInspectorFrontendHost, noInspectorFrontendHost, gTypeInspectorFrontendHost
, IntersectionObserver(IntersectionObserver), unIntersectionObserver, noIntersectionObserver, gTypeIntersectionObserver
, IntersectionObserverEntry(IntersectionObserverEntry), unIntersectionObserverEntry, noIntersectionObserverEntry, gTypeIntersectionObserverEntry
, IntersectionObserverEntryInit(IntersectionObserverEntryInit), unIntersectionObserverEntryInit, noIntersectionObserverEntryInit, gTypeIntersectionObserverEntryInit
, IntersectionObserverInit(IntersectionObserverInit), unIntersectionObserverInit, noIntersectionObserverInit, gTypeIntersectionObserverInit
, JsonWebKey(JsonWebKey), unJsonWebKey, noJsonWebKey, gTypeJsonWebKey
, KeyboardEvent(KeyboardEvent), unKeyboardEvent, noKeyboardEvent, gTypeKeyboardEvent
, KeyboardEventInit(KeyboardEventInit), unKeyboardEventInit, noKeyboardEventInit, gTypeKeyboardEventInit
, KeyframeEffect(KeyframeEffect), unKeyframeEffect, noKeyframeEffect, gTypeKeyframeEffect
, Location(Location), unLocation, noLocation, gTypeLocation
, LongRange(LongRange), unLongRange, IsLongRange, toLongRange, noLongRange, gTypeLongRange
, MediaController(MediaController), unMediaController, noMediaController, gTypeMediaController
, MediaControlsHost(MediaControlsHost), unMediaControlsHost, noMediaControlsHost, gTypeMediaControlsHost
, MediaDeviceInfo(MediaDeviceInfo), unMediaDeviceInfo, noMediaDeviceInfo, gTypeMediaDeviceInfo
, MediaDevices(MediaDevices), unMediaDevices, noMediaDevices, gTypeMediaDevices
, MediaElementAudioSourceNode(MediaElementAudioSourceNode), unMediaElementAudioSourceNode, noMediaElementAudioSourceNode, gTypeMediaElementAudioSourceNode
, MediaEncryptedEvent(MediaEncryptedEvent), unMediaEncryptedEvent, noMediaEncryptedEvent, gTypeMediaEncryptedEvent
, MediaEncryptedEventInit(MediaEncryptedEventInit), unMediaEncryptedEventInit, noMediaEncryptedEventInit, gTypeMediaEncryptedEventInit
, MediaError(MediaError), unMediaError, noMediaError, gTypeMediaError
, MediaKeyMessageEvent(MediaKeyMessageEvent), unMediaKeyMessageEvent, noMediaKeyMessageEvent, gTypeMediaKeyMessageEvent
, MediaKeyMessageEventInit(MediaKeyMessageEventInit), unMediaKeyMessageEventInit, noMediaKeyMessageEventInit, gTypeMediaKeyMessageEventInit
, MediaKeySession(MediaKeySession), unMediaKeySession, noMediaKeySession, gTypeMediaKeySession
, MediaKeyStatusMap(MediaKeyStatusMap), unMediaKeyStatusMap, noMediaKeyStatusMap, gTypeMediaKeyStatusMap
, MediaKeySystemAccess(MediaKeySystemAccess), unMediaKeySystemAccess, noMediaKeySystemAccess, gTypeMediaKeySystemAccess
, MediaKeySystemConfiguration(MediaKeySystemConfiguration), unMediaKeySystemConfiguration, noMediaKeySystemConfiguration, gTypeMediaKeySystemConfiguration
, MediaKeySystemMediaCapability(MediaKeySystemMediaCapability), unMediaKeySystemMediaCapability, noMediaKeySystemMediaCapability, gTypeMediaKeySystemMediaCapability
, MediaKeys(MediaKeys), unMediaKeys, noMediaKeys, gTypeMediaKeys
, MediaList(MediaList), unMediaList, noMediaList, gTypeMediaList
, MediaMetadata(MediaMetadata), unMediaMetadata, noMediaMetadata, gTypeMediaMetadata
, MediaQueryList(MediaQueryList), unMediaQueryList, noMediaQueryList, gTypeMediaQueryList
, MediaRemoteControls(MediaRemoteControls), unMediaRemoteControls, noMediaRemoteControls, gTypeMediaRemoteControls
, MediaSession(MediaSession), unMediaSession, noMediaSession, gTypeMediaSession
, MediaSource(MediaSource), unMediaSource, noMediaSource, gTypeMediaSource
, MediaStream(MediaStream), unMediaStream, noMediaStream, gTypeMediaStream
, MediaStreamAudioDestinationNode(MediaStreamAudioDestinationNode), unMediaStreamAudioDestinationNode, noMediaStreamAudioDestinationNode, gTypeMediaStreamAudioDestinationNode
, MediaStreamAudioSourceNode(MediaStreamAudioSourceNode), unMediaStreamAudioSourceNode, noMediaStreamAudioSourceNode, gTypeMediaStreamAudioSourceNode
, MediaStreamConstraints(MediaStreamConstraints), unMediaStreamConstraints, noMediaStreamConstraints, gTypeMediaStreamConstraints
, MediaStreamEvent(MediaStreamEvent), unMediaStreamEvent, noMediaStreamEvent, gTypeMediaStreamEvent
, MediaStreamEventInit(MediaStreamEventInit), unMediaStreamEventInit, noMediaStreamEventInit, gTypeMediaStreamEventInit
, MediaStreamTrack(MediaStreamTrack), unMediaStreamTrack, IsMediaStreamTrack, toMediaStreamTrack, noMediaStreamTrack, gTypeMediaStreamTrack
, MediaStreamTrackEvent(MediaStreamTrackEvent), unMediaStreamTrackEvent, noMediaStreamTrackEvent, gTypeMediaStreamTrackEvent
, MediaStreamTrackEventInit(MediaStreamTrackEventInit), unMediaStreamTrackEventInit, noMediaStreamTrackEventInit, gTypeMediaStreamTrackEventInit
, MediaTrackCapabilities(MediaTrackCapabilities), unMediaTrackCapabilities, noMediaTrackCapabilities, gTypeMediaTrackCapabilities
, MediaTrackConstraintSet(MediaTrackConstraintSet), unMediaTrackConstraintSet, IsMediaTrackConstraintSet, toMediaTrackConstraintSet, noMediaTrackConstraintSet, gTypeMediaTrackConstraintSet
, MediaTrackConstraints(MediaTrackConstraints), unMediaTrackConstraints, noMediaTrackConstraints, gTypeMediaTrackConstraints
, MediaTrackSettings(MediaTrackSettings), unMediaTrackSettings, noMediaTrackSettings, gTypeMediaTrackSettings
, MediaTrackSupportedConstraints(MediaTrackSupportedConstraints), unMediaTrackSupportedConstraints, noMediaTrackSupportedConstraints, gTypeMediaTrackSupportedConstraints
, MessageChannel(MessageChannel), unMessageChannel, noMessageChannel, gTypeMessageChannel
, MessageEvent(MessageEvent), unMessageEvent, noMessageEvent, gTypeMessageEvent
, MessageEventInit(MessageEventInit), unMessageEventInit, noMessageEventInit, gTypeMessageEventInit
, MessagePort(MessagePort), unMessagePort, noMessagePort, gTypeMessagePort
, MimeType(MimeType), unMimeType, noMimeType, gTypeMimeType
, MimeTypeArray(MimeTypeArray), unMimeTypeArray, noMimeTypeArray, gTypeMimeTypeArray
, MouseEvent(MouseEvent), unMouseEvent, IsMouseEvent, toMouseEvent, noMouseEvent, gTypeMouseEvent
, MouseEventInit(MouseEventInit), unMouseEventInit, IsMouseEventInit, toMouseEventInit, noMouseEventInit, gTypeMouseEventInit
, MutationEvent(MutationEvent), unMutationEvent, noMutationEvent, gTypeMutationEvent
, MutationObserver(MutationObserver), unMutationObserver, noMutationObserver, gTypeMutationObserver
, MutationObserverInit(MutationObserverInit), unMutationObserverInit, noMutationObserverInit, gTypeMutationObserverInit
, MutationRecord(MutationRecord), unMutationRecord, noMutationRecord, gTypeMutationRecord
, NamedNodeMap(NamedNodeMap), unNamedNodeMap, noNamedNodeMap, gTypeNamedNodeMap
, Navigator(Navigator), unNavigator, noNavigator, gTypeNavigator
, NavigatorConcurrentHardware(NavigatorConcurrentHardware), unNavigatorConcurrentHardware, IsNavigatorConcurrentHardware, toNavigatorConcurrentHardware, noNavigatorConcurrentHardware, gTypeNavigatorConcurrentHardware
, NavigatorID(NavigatorID), unNavigatorID, IsNavigatorID, toNavigatorID, noNavigatorID, gTypeNavigatorID
, NavigatorLanguage(NavigatorLanguage), unNavigatorLanguage, IsNavigatorLanguage, toNavigatorLanguage, noNavigatorLanguage, gTypeNavigatorLanguage
, NavigatorOnLine(NavigatorOnLine), unNavigatorOnLine, IsNavigatorOnLine, toNavigatorOnLine, noNavigatorOnLine, gTypeNavigatorOnLine
, NavigatorUserMediaError(NavigatorUserMediaError), unNavigatorUserMediaError, noNavigatorUserMediaError, gTypeNavigatorUserMediaError
, Node(Node), unNode, IsNode, toNode, noNode, gTypeNode
, NodeIterator(NodeIterator), unNodeIterator, noNodeIterator, gTypeNodeIterator
, NodeList(NodeList), unNodeList, IsNodeList, toNodeList, noNodeList, gTypeNodeList
, NonDocumentTypeChildNode(NonDocumentTypeChildNode), unNonDocumentTypeChildNode, IsNonDocumentTypeChildNode, toNonDocumentTypeChildNode, noNonDocumentTypeChildNode, gTypeNonDocumentTypeChildNode
, NonElementParentNode(NonElementParentNode), unNonElementParentNode, IsNonElementParentNode, toNonElementParentNode, noNonElementParentNode, gTypeNonElementParentNode
, Notification(Notification), unNotification, noNotification, gTypeNotification
, NotificationOptions(NotificationOptions), unNotificationOptions, noNotificationOptions, gTypeNotificationOptions
, OESElementIndexUint(OESElementIndexUint), unOESElementIndexUint, noOESElementIndexUint, gTypeOESElementIndexUint
, OESStandardDerivatives(OESStandardDerivatives), unOESStandardDerivatives, noOESStandardDerivatives, gTypeOESStandardDerivatives
, OESTextureFloat(OESTextureFloat), unOESTextureFloat, noOESTextureFloat, gTypeOESTextureFloat
, OESTextureFloatLinear(OESTextureFloatLinear), unOESTextureFloatLinear, noOESTextureFloatLinear, gTypeOESTextureFloatLinear
, OESTextureHalfFloat(OESTextureHalfFloat), unOESTextureHalfFloat, noOESTextureHalfFloat, gTypeOESTextureHalfFloat
, OESTextureHalfFloatLinear(OESTextureHalfFloatLinear), unOESTextureHalfFloatLinear, noOESTextureHalfFloatLinear, gTypeOESTextureHalfFloatLinear
, OESVertexArrayObject(OESVertexArrayObject), unOESVertexArrayObject, noOESVertexArrayObject, gTypeOESVertexArrayObject
, OfflineAudioCompletionEvent(OfflineAudioCompletionEvent), unOfflineAudioCompletionEvent, noOfflineAudioCompletionEvent, gTypeOfflineAudioCompletionEvent
, OfflineAudioContext(OfflineAudioContext), unOfflineAudioContext, noOfflineAudioContext, gTypeOfflineAudioContext
, OscillatorNode(OscillatorNode), unOscillatorNode, noOscillatorNode, gTypeOscillatorNode
, OverconstrainedError(OverconstrainedError), unOverconstrainedError, noOverconstrainedError, gTypeOverconstrainedError
, OverconstrainedErrorEvent(OverconstrainedErrorEvent), unOverconstrainedErrorEvent, noOverconstrainedErrorEvent, gTypeOverconstrainedErrorEvent
, OverconstrainedErrorEventInit(OverconstrainedErrorEventInit), unOverconstrainedErrorEventInit, noOverconstrainedErrorEventInit, gTypeOverconstrainedErrorEventInit
, OverflowEvent(OverflowEvent), unOverflowEvent, noOverflowEvent, gTypeOverflowEvent
, OverflowEventInit(OverflowEventInit), unOverflowEventInit, noOverflowEventInit, gTypeOverflowEventInit
, PageTransitionEvent(PageTransitionEvent), unPageTransitionEvent, noPageTransitionEvent, gTypePageTransitionEvent
, PageTransitionEventInit(PageTransitionEventInit), unPageTransitionEventInit, noPageTransitionEventInit, gTypePageTransitionEventInit
, PannerNode(PannerNode), unPannerNode, noPannerNode, gTypePannerNode
, ParentNode(ParentNode), unParentNode, IsParentNode, toParentNode, noParentNode, gTypeParentNode
, PasswordCredential(PasswordCredential), unPasswordCredential, noPasswordCredential, gTypePasswordCredential
, PasswordCredentialData(PasswordCredentialData), unPasswordCredentialData, noPasswordCredentialData, gTypePasswordCredentialData
, Path2D(Path2D), unPath2D, noPath2D, gTypePath2D
, Pbkdf2Params(Pbkdf2Params), unPbkdf2Params, noPbkdf2Params, gTypePbkdf2Params
, Performance(Performance), unPerformance, noPerformance, gTypePerformance
, PerformanceEntry(PerformanceEntry), unPerformanceEntry, IsPerformanceEntry, toPerformanceEntry, noPerformanceEntry, gTypePerformanceEntry
, PerformanceMark(PerformanceMark), unPerformanceMark, noPerformanceMark, gTypePerformanceMark
, PerformanceMeasure(PerformanceMeasure), unPerformanceMeasure, noPerformanceMeasure, gTypePerformanceMeasure
, PerformanceNavigation(PerformanceNavigation), unPerformanceNavigation, noPerformanceNavigation, gTypePerformanceNavigation
, PerformanceObserver(PerformanceObserver), unPerformanceObserver, noPerformanceObserver, gTypePerformanceObserver
, PerformanceObserverEntryList(PerformanceObserverEntryList), unPerformanceObserverEntryList, noPerformanceObserverEntryList, gTypePerformanceObserverEntryList
, PerformanceObserverInit(PerformanceObserverInit), unPerformanceObserverInit, noPerformanceObserverInit, gTypePerformanceObserverInit
, PerformanceResourceTiming(PerformanceResourceTiming), unPerformanceResourceTiming, noPerformanceResourceTiming, gTypePerformanceResourceTiming
, PerformanceTiming(PerformanceTiming), unPerformanceTiming, noPerformanceTiming, gTypePerformanceTiming
, PeriodicWave(PeriodicWave), unPeriodicWave, noPeriodicWave, gTypePeriodicWave
, Plugin(Plugin), unPlugin, noPlugin, gTypePlugin
, PluginArray(PluginArray), unPluginArray, noPluginArray, gTypePluginArray
, PopStateEvent(PopStateEvent), unPopStateEvent, noPopStateEvent, gTypePopStateEvent
, PopStateEventInit(PopStateEventInit), unPopStateEventInit, noPopStateEventInit, gTypePopStateEventInit
, PositionError(PositionError), unPositionError, noPositionError, gTypePositionError
, PositionOptions(PositionOptions), unPositionOptions, noPositionOptions, gTypePositionOptions
, ProcessingInstruction(ProcessingInstruction), unProcessingInstruction, noProcessingInstruction, gTypeProcessingInstruction
, ProgressEvent(ProgressEvent), unProgressEvent, IsProgressEvent, toProgressEvent, noProgressEvent, gTypeProgressEvent
, ProgressEventInit(ProgressEventInit), unProgressEventInit, noProgressEventInit, gTypeProgressEventInit
, PromiseRejectionEvent(PromiseRejectionEvent), unPromiseRejectionEvent, noPromiseRejectionEvent, gTypePromiseRejectionEvent
, PromiseRejectionEventInit(PromiseRejectionEventInit), unPromiseRejectionEventInit, noPromiseRejectionEventInit, gTypePromiseRejectionEventInit
, QuickTimePluginReplacement(QuickTimePluginReplacement), unQuickTimePluginReplacement, noQuickTimePluginReplacement, gTypeQuickTimePluginReplacement
, RGBColor(RGBColor), unRGBColor, noRGBColor, gTypeRGBColor
, RTCAnswerOptions(RTCAnswerOptions), unRTCAnswerOptions, noRTCAnswerOptions, gTypeRTCAnswerOptions
, RTCConfiguration(RTCConfiguration), unRTCConfiguration, noRTCConfiguration, gTypeRTCConfiguration
, RTCDTMFSender(RTCDTMFSender), unRTCDTMFSender, noRTCDTMFSender, gTypeRTCDTMFSender
, RTCDTMFToneChangeEvent(RTCDTMFToneChangeEvent), unRTCDTMFToneChangeEvent, noRTCDTMFToneChangeEvent, gTypeRTCDTMFToneChangeEvent
, RTCDTMFToneChangeEventInit(RTCDTMFToneChangeEventInit), unRTCDTMFToneChangeEventInit, noRTCDTMFToneChangeEventInit, gTypeRTCDTMFToneChangeEventInit
, RTCDataChannel(RTCDataChannel), unRTCDataChannel, noRTCDataChannel, gTypeRTCDataChannel
, RTCDataChannelEvent(RTCDataChannelEvent), unRTCDataChannelEvent, noRTCDataChannelEvent, gTypeRTCDataChannelEvent
, RTCDataChannelEventInit(RTCDataChannelEventInit), unRTCDataChannelEventInit, noRTCDataChannelEventInit, gTypeRTCDataChannelEventInit
, RTCDataChannelInit(RTCDataChannelInit), unRTCDataChannelInit, noRTCDataChannelInit, gTypeRTCDataChannelInit
, RTCDataChannelStats(RTCDataChannelStats), unRTCDataChannelStats, noRTCDataChannelStats, gTypeRTCDataChannelStats
, RTCIceCandidate(RTCIceCandidate), unRTCIceCandidate, noRTCIceCandidate, gTypeRTCIceCandidate
, RTCIceCandidateEvent(RTCIceCandidateEvent), unRTCIceCandidateEvent, noRTCIceCandidateEvent, gTypeRTCIceCandidateEvent
, RTCIceCandidateInit(RTCIceCandidateInit), unRTCIceCandidateInit, noRTCIceCandidateInit, gTypeRTCIceCandidateInit
, RTCIceServer(RTCIceServer), unRTCIceServer, noRTCIceServer, gTypeRTCIceServer
, RTCIceTransport(RTCIceTransport), unRTCIceTransport, noRTCIceTransport, gTypeRTCIceTransport
, RTCInboundRTPStreamStats(RTCInboundRTPStreamStats), unRTCInboundRTPStreamStats, noRTCInboundRTPStreamStats, gTypeRTCInboundRTPStreamStats
, RTCMediaStreamTrackStats(RTCMediaStreamTrackStats), unRTCMediaStreamTrackStats, noRTCMediaStreamTrackStats, gTypeRTCMediaStreamTrackStats
, RTCOfferAnswerOptions(RTCOfferAnswerOptions), unRTCOfferAnswerOptions, IsRTCOfferAnswerOptions, toRTCOfferAnswerOptions, noRTCOfferAnswerOptions, gTypeRTCOfferAnswerOptions
, RTCOfferOptions(RTCOfferOptions), unRTCOfferOptions, noRTCOfferOptions, gTypeRTCOfferOptions
, RTCOutboundRTPStreamStats(RTCOutboundRTPStreamStats), unRTCOutboundRTPStreamStats, noRTCOutboundRTPStreamStats, gTypeRTCOutboundRTPStreamStats
, RTCPeerConnection(RTCPeerConnection), unRTCPeerConnection, noRTCPeerConnection, gTypeRTCPeerConnection
, RTCPeerConnectionIceEvent(RTCPeerConnectionIceEvent), unRTCPeerConnectionIceEvent, noRTCPeerConnectionIceEvent, gTypeRTCPeerConnectionIceEvent
, RTCRTPStreamStats(RTCRTPStreamStats), unRTCRTPStreamStats, IsRTCRTPStreamStats, toRTCRTPStreamStats, noRTCRTPStreamStats, gTypeRTCRTPStreamStats
, RTCRtpCodecParameters(RTCRtpCodecParameters), unRTCRtpCodecParameters, noRTCRtpCodecParameters, gTypeRTCRtpCodecParameters
, RTCRtpEncodingParameters(RTCRtpEncodingParameters), unRTCRtpEncodingParameters, noRTCRtpEncodingParameters, gTypeRTCRtpEncodingParameters
, RTCRtpFecParameters(RTCRtpFecParameters), unRTCRtpFecParameters, noRTCRtpFecParameters, gTypeRTCRtpFecParameters
, RTCRtpHeaderExtensionParameters(RTCRtpHeaderExtensionParameters), unRTCRtpHeaderExtensionParameters, noRTCRtpHeaderExtensionParameters, gTypeRTCRtpHeaderExtensionParameters
, RTCRtpParameters(RTCRtpParameters), unRTCRtpParameters, noRTCRtpParameters, gTypeRTCRtpParameters
, RTCRtpReceiver(RTCRtpReceiver), unRTCRtpReceiver, noRTCRtpReceiver, gTypeRTCRtpReceiver
, RTCRtpRtxParameters(RTCRtpRtxParameters), unRTCRtpRtxParameters, noRTCRtpRtxParameters, gTypeRTCRtpRtxParameters
, RTCRtpSender(RTCRtpSender), unRTCRtpSender, noRTCRtpSender, gTypeRTCRtpSender
, RTCRtpTransceiver(RTCRtpTransceiver), unRTCRtpTransceiver, noRTCRtpTransceiver, gTypeRTCRtpTransceiver
, RTCRtpTransceiverInit(RTCRtpTransceiverInit), unRTCRtpTransceiverInit, noRTCRtpTransceiverInit, gTypeRTCRtpTransceiverInit
, RTCSessionDescription(RTCSessionDescription), unRTCSessionDescription, noRTCSessionDescription, gTypeRTCSessionDescription
, RTCSessionDescriptionInit(RTCSessionDescriptionInit), unRTCSessionDescriptionInit, noRTCSessionDescriptionInit, gTypeRTCSessionDescriptionInit
, RTCStats(RTCStats), unRTCStats, IsRTCStats, toRTCStats, noRTCStats, gTypeRTCStats
, RTCStatsReport(RTCStatsReport), unRTCStatsReport, noRTCStatsReport, gTypeRTCStatsReport
, RTCTrackEvent(RTCTrackEvent), unRTCTrackEvent, noRTCTrackEvent, gTypeRTCTrackEvent
, RTCTrackEventInit(RTCTrackEventInit), unRTCTrackEventInit, noRTCTrackEventInit, gTypeRTCTrackEventInit
, RadioNodeList(RadioNodeList), unRadioNodeList, noRadioNodeList, gTypeRadioNodeList
, Range(Range), unRange, noRange, gTypeRange
, ReadableByteStreamController(ReadableByteStreamController), unReadableByteStreamController, noReadableByteStreamController, gTypeReadableByteStreamController
, ReadableStream(ReadableStream), unReadableStream, noReadableStream, gTypeReadableStream
, ReadableStreamBYOBReader(ReadableStreamBYOBReader), unReadableStreamBYOBReader, noReadableStreamBYOBReader, gTypeReadableStreamBYOBReader
, ReadableStreamBYOBRequest(ReadableStreamBYOBRequest), unReadableStreamBYOBRequest, noReadableStreamBYOBRequest, gTypeReadableStreamBYOBRequest
, ReadableStreamDefaultController(ReadableStreamDefaultController), unReadableStreamDefaultController, noReadableStreamDefaultController, gTypeReadableStreamDefaultController
, ReadableStreamDefaultReader(ReadableStreamDefaultReader), unReadableStreamDefaultReader, noReadableStreamDefaultReader, gTypeReadableStreamDefaultReader
, ReadableStreamSource(ReadableStreamSource), unReadableStreamSource, noReadableStreamSource, gTypeReadableStreamSource
, Rect(Rect), unRect, noRect, gTypeRect
, Request(Request), unRequest, noRequest, gTypeRequest
, RequestInit(RequestInit), unRequestInit, noRequestInit, gTypeRequestInit
, Response(Response), unResponse, noResponse, gTypeResponse
, RotationRate(RotationRate), unRotationRate, noRotationRate, gTypeRotationRate
, RsaHashedImportParams(RsaHashedImportParams), unRsaHashedImportParams, noRsaHashedImportParams, gTypeRsaHashedImportParams
, RsaHashedKeyGenParams(RsaHashedKeyGenParams), unRsaHashedKeyGenParams, noRsaHashedKeyGenParams, gTypeRsaHashedKeyGenParams
, RsaKeyGenParams(RsaKeyGenParams), unRsaKeyGenParams, IsRsaKeyGenParams, toRsaKeyGenParams, noRsaKeyGenParams, gTypeRsaKeyGenParams
, RsaOaepParams(RsaOaepParams), unRsaOaepParams, noRsaOaepParams, gTypeRsaOaepParams
, RsaOtherPrimesInfo(RsaOtherPrimesInfo), unRsaOtherPrimesInfo, noRsaOtherPrimesInfo, gTypeRsaOtherPrimesInfo
, SQLError(SQLError), unSQLError, noSQLError, gTypeSQLError
, SQLException(SQLException), unSQLException, noSQLException, gTypeSQLException
, SQLResultSet(SQLResultSet), unSQLResultSet, noSQLResultSet, gTypeSQLResultSet
, SQLResultSetRowList(SQLResultSetRowList), unSQLResultSetRowList, noSQLResultSetRowList, gTypeSQLResultSetRowList
, SQLTransaction(SQLTransaction), unSQLTransaction, noSQLTransaction, gTypeSQLTransaction
, SVGAElement(SVGAElement), unSVGAElement, noSVGAElement, gTypeSVGAElement
, SVGAltGlyphDefElement(SVGAltGlyphDefElement), unSVGAltGlyphDefElement, noSVGAltGlyphDefElement, gTypeSVGAltGlyphDefElement
, SVGAltGlyphElement(SVGAltGlyphElement), unSVGAltGlyphElement, noSVGAltGlyphElement, gTypeSVGAltGlyphElement
, SVGAltGlyphItemElement(SVGAltGlyphItemElement), unSVGAltGlyphItemElement, noSVGAltGlyphItemElement, gTypeSVGAltGlyphItemElement
, SVGAngle(SVGAngle), unSVGAngle, noSVGAngle, gTypeSVGAngle
, SVGAnimateColorElement(SVGAnimateColorElement), unSVGAnimateColorElement, noSVGAnimateColorElement, gTypeSVGAnimateColorElement
, SVGAnimateElement(SVGAnimateElement), unSVGAnimateElement, noSVGAnimateElement, gTypeSVGAnimateElement
, SVGAnimateMotionElement(SVGAnimateMotionElement), unSVGAnimateMotionElement, noSVGAnimateMotionElement, gTypeSVGAnimateMotionElement
, SVGAnimateTransformElement(SVGAnimateTransformElement), unSVGAnimateTransformElement, noSVGAnimateTransformElement, gTypeSVGAnimateTransformElement
, SVGAnimatedAngle(SVGAnimatedAngle), unSVGAnimatedAngle, noSVGAnimatedAngle, gTypeSVGAnimatedAngle
, SVGAnimatedBoolean(SVGAnimatedBoolean), unSVGAnimatedBoolean, noSVGAnimatedBoolean, gTypeSVGAnimatedBoolean
, SVGAnimatedEnumeration(SVGAnimatedEnumeration), unSVGAnimatedEnumeration, noSVGAnimatedEnumeration, gTypeSVGAnimatedEnumeration
, SVGAnimatedInteger(SVGAnimatedInteger), unSVGAnimatedInteger, noSVGAnimatedInteger, gTypeSVGAnimatedInteger
, SVGAnimatedLength(SVGAnimatedLength), unSVGAnimatedLength, noSVGAnimatedLength, gTypeSVGAnimatedLength
, SVGAnimatedLengthList(SVGAnimatedLengthList), unSVGAnimatedLengthList, noSVGAnimatedLengthList, gTypeSVGAnimatedLengthList
, SVGAnimatedNumber(SVGAnimatedNumber), unSVGAnimatedNumber, noSVGAnimatedNumber, gTypeSVGAnimatedNumber
, SVGAnimatedNumberList(SVGAnimatedNumberList), unSVGAnimatedNumberList, noSVGAnimatedNumberList, gTypeSVGAnimatedNumberList
, SVGAnimatedPreserveAspectRatio(SVGAnimatedPreserveAspectRatio), unSVGAnimatedPreserveAspectRatio, noSVGAnimatedPreserveAspectRatio, gTypeSVGAnimatedPreserveAspectRatio
, SVGAnimatedRect(SVGAnimatedRect), unSVGAnimatedRect, noSVGAnimatedRect, gTypeSVGAnimatedRect
, SVGAnimatedString(SVGAnimatedString), unSVGAnimatedString, noSVGAnimatedString, gTypeSVGAnimatedString
, SVGAnimatedTransformList(SVGAnimatedTransformList), unSVGAnimatedTransformList, noSVGAnimatedTransformList, gTypeSVGAnimatedTransformList
, SVGAnimationElement(SVGAnimationElement), unSVGAnimationElement, IsSVGAnimationElement, toSVGAnimationElement, noSVGAnimationElement, gTypeSVGAnimationElement
, SVGCircleElement(SVGCircleElement), unSVGCircleElement, noSVGCircleElement, gTypeSVGCircleElement
, SVGClipPathElement(SVGClipPathElement), unSVGClipPathElement, noSVGClipPathElement, gTypeSVGClipPathElement
, SVGComponentTransferFunctionElement(SVGComponentTransferFunctionElement), unSVGComponentTransferFunctionElement, IsSVGComponentTransferFunctionElement, toSVGComponentTransferFunctionElement, noSVGComponentTransferFunctionElement, gTypeSVGComponentTransferFunctionElement
, SVGCursorElement(SVGCursorElement), unSVGCursorElement, noSVGCursorElement, gTypeSVGCursorElement
, SVGDefsElement(SVGDefsElement), unSVGDefsElement, noSVGDefsElement, gTypeSVGDefsElement
, SVGDescElement(SVGDescElement), unSVGDescElement, noSVGDescElement, gTypeSVGDescElement
, SVGElement(SVGElement), unSVGElement, IsSVGElement, toSVGElement, noSVGElement, gTypeSVGElement
, SVGEllipseElement(SVGEllipseElement), unSVGEllipseElement, noSVGEllipseElement, gTypeSVGEllipseElement
, SVGException(SVGException), unSVGException, noSVGException, gTypeSVGException
, SVGExternalResourcesRequired(SVGExternalResourcesRequired), unSVGExternalResourcesRequired, IsSVGExternalResourcesRequired, toSVGExternalResourcesRequired, noSVGExternalResourcesRequired, gTypeSVGExternalResourcesRequired
, SVGFEBlendElement(SVGFEBlendElement), unSVGFEBlendElement, noSVGFEBlendElement, gTypeSVGFEBlendElement
, SVGFEColorMatrixElement(SVGFEColorMatrixElement), unSVGFEColorMatrixElement, noSVGFEColorMatrixElement, gTypeSVGFEColorMatrixElement
, SVGFEComponentTransferElement(SVGFEComponentTransferElement), unSVGFEComponentTransferElement, noSVGFEComponentTransferElement, gTypeSVGFEComponentTransferElement
, SVGFECompositeElement(SVGFECompositeElement), unSVGFECompositeElement, noSVGFECompositeElement, gTypeSVGFECompositeElement
, SVGFEConvolveMatrixElement(SVGFEConvolveMatrixElement), unSVGFEConvolveMatrixElement, noSVGFEConvolveMatrixElement, gTypeSVGFEConvolveMatrixElement
, SVGFEDiffuseLightingElement(SVGFEDiffuseLightingElement), unSVGFEDiffuseLightingElement, noSVGFEDiffuseLightingElement, gTypeSVGFEDiffuseLightingElement
, SVGFEDisplacementMapElement(SVGFEDisplacementMapElement), unSVGFEDisplacementMapElement, noSVGFEDisplacementMapElement, gTypeSVGFEDisplacementMapElement
, SVGFEDistantLightElement(SVGFEDistantLightElement), unSVGFEDistantLightElement, noSVGFEDistantLightElement, gTypeSVGFEDistantLightElement
, SVGFEDropShadowElement(SVGFEDropShadowElement), unSVGFEDropShadowElement, noSVGFEDropShadowElement, gTypeSVGFEDropShadowElement
, SVGFEFloodElement(SVGFEFloodElement), unSVGFEFloodElement, noSVGFEFloodElement, gTypeSVGFEFloodElement
, SVGFEFuncAElement(SVGFEFuncAElement), unSVGFEFuncAElement, noSVGFEFuncAElement, gTypeSVGFEFuncAElement
, SVGFEFuncBElement(SVGFEFuncBElement), unSVGFEFuncBElement, noSVGFEFuncBElement, gTypeSVGFEFuncBElement
, SVGFEFuncGElement(SVGFEFuncGElement), unSVGFEFuncGElement, noSVGFEFuncGElement, gTypeSVGFEFuncGElement
, SVGFEFuncRElement(SVGFEFuncRElement), unSVGFEFuncRElement, noSVGFEFuncRElement, gTypeSVGFEFuncRElement
, SVGFEGaussianBlurElement(SVGFEGaussianBlurElement), unSVGFEGaussianBlurElement, noSVGFEGaussianBlurElement, gTypeSVGFEGaussianBlurElement
, SVGFEImageElement(SVGFEImageElement), unSVGFEImageElement, noSVGFEImageElement, gTypeSVGFEImageElement
, SVGFEMergeElement(SVGFEMergeElement), unSVGFEMergeElement, noSVGFEMergeElement, gTypeSVGFEMergeElement
, SVGFEMergeNodeElement(SVGFEMergeNodeElement), unSVGFEMergeNodeElement, noSVGFEMergeNodeElement, gTypeSVGFEMergeNodeElement
, SVGFEMorphologyElement(SVGFEMorphologyElement), unSVGFEMorphologyElement, noSVGFEMorphologyElement, gTypeSVGFEMorphologyElement
, SVGFEOffsetElement(SVGFEOffsetElement), unSVGFEOffsetElement, noSVGFEOffsetElement, gTypeSVGFEOffsetElement
, SVGFEPointLightElement(SVGFEPointLightElement), unSVGFEPointLightElement, noSVGFEPointLightElement, gTypeSVGFEPointLightElement
, SVGFESpecularLightingElement(SVGFESpecularLightingElement), unSVGFESpecularLightingElement, noSVGFESpecularLightingElement, gTypeSVGFESpecularLightingElement
, SVGFESpotLightElement(SVGFESpotLightElement), unSVGFESpotLightElement, noSVGFESpotLightElement, gTypeSVGFESpotLightElement
, SVGFETileElement(SVGFETileElement), unSVGFETileElement, noSVGFETileElement, gTypeSVGFETileElement
, SVGFETurbulenceElement(SVGFETurbulenceElement), unSVGFETurbulenceElement, noSVGFETurbulenceElement, gTypeSVGFETurbulenceElement
, SVGFilterElement(SVGFilterElement), unSVGFilterElement, noSVGFilterElement, gTypeSVGFilterElement
, SVGFilterPrimitiveStandardAttributes(SVGFilterPrimitiveStandardAttributes), unSVGFilterPrimitiveStandardAttributes, IsSVGFilterPrimitiveStandardAttributes, toSVGFilterPrimitiveStandardAttributes, noSVGFilterPrimitiveStandardAttributes, gTypeSVGFilterPrimitiveStandardAttributes
, SVGFitToViewBox(SVGFitToViewBox), unSVGFitToViewBox, IsSVGFitToViewBox, toSVGFitToViewBox, noSVGFitToViewBox, gTypeSVGFitToViewBox
, SVGFontElement(SVGFontElement), unSVGFontElement, noSVGFontElement, gTypeSVGFontElement
, SVGFontFaceElement(SVGFontFaceElement), unSVGFontFaceElement, noSVGFontFaceElement, gTypeSVGFontFaceElement
, SVGFontFaceFormatElement(SVGFontFaceFormatElement), unSVGFontFaceFormatElement, noSVGFontFaceFormatElement, gTypeSVGFontFaceFormatElement
, SVGFontFaceNameElement(SVGFontFaceNameElement), unSVGFontFaceNameElement, noSVGFontFaceNameElement, gTypeSVGFontFaceNameElement
, SVGFontFaceSrcElement(SVGFontFaceSrcElement), unSVGFontFaceSrcElement, noSVGFontFaceSrcElement, gTypeSVGFontFaceSrcElement
, SVGFontFaceUriElement(SVGFontFaceUriElement), unSVGFontFaceUriElement, noSVGFontFaceUriElement, gTypeSVGFontFaceUriElement
, SVGForeignObjectElement(SVGForeignObjectElement), unSVGForeignObjectElement, noSVGForeignObjectElement, gTypeSVGForeignObjectElement
, SVGGElement(SVGGElement), unSVGGElement, noSVGGElement, gTypeSVGGElement
, SVGGlyphElement(SVGGlyphElement), unSVGGlyphElement, noSVGGlyphElement, gTypeSVGGlyphElement
, SVGGlyphRefElement(SVGGlyphRefElement), unSVGGlyphRefElement, noSVGGlyphRefElement, gTypeSVGGlyphRefElement
, SVGGradientElement(SVGGradientElement), unSVGGradientElement, IsSVGGradientElement, toSVGGradientElement, noSVGGradientElement, gTypeSVGGradientElement
, SVGGraphicsElement(SVGGraphicsElement), unSVGGraphicsElement, IsSVGGraphicsElement, toSVGGraphicsElement, noSVGGraphicsElement, gTypeSVGGraphicsElement
, SVGHKernElement(SVGHKernElement), unSVGHKernElement, noSVGHKernElement, gTypeSVGHKernElement
, SVGImageElement(SVGImageElement), unSVGImageElement, noSVGImageElement, gTypeSVGImageElement
, SVGLength(SVGLength), unSVGLength, noSVGLength, gTypeSVGLength
, SVGLengthList(SVGLengthList), unSVGLengthList, noSVGLengthList, gTypeSVGLengthList
, SVGLineElement(SVGLineElement), unSVGLineElement, noSVGLineElement, gTypeSVGLineElement
, SVGLinearGradientElement(SVGLinearGradientElement), unSVGLinearGradientElement, noSVGLinearGradientElement, gTypeSVGLinearGradientElement
, SVGMPathElement(SVGMPathElement), unSVGMPathElement, noSVGMPathElement, gTypeSVGMPathElement
, SVGMarkerElement(SVGMarkerElement), unSVGMarkerElement, noSVGMarkerElement, gTypeSVGMarkerElement
, SVGMaskElement(SVGMaskElement), unSVGMaskElement, noSVGMaskElement, gTypeSVGMaskElement
, SVGMatrix(SVGMatrix), unSVGMatrix, noSVGMatrix, gTypeSVGMatrix
, SVGMetadataElement(SVGMetadataElement), unSVGMetadataElement, noSVGMetadataElement, gTypeSVGMetadataElement
, SVGMissingGlyphElement(SVGMissingGlyphElement), unSVGMissingGlyphElement, noSVGMissingGlyphElement, gTypeSVGMissingGlyphElement
, SVGNumber(SVGNumber), unSVGNumber, noSVGNumber, gTypeSVGNumber
, SVGNumberList(SVGNumberList), unSVGNumberList, noSVGNumberList, gTypeSVGNumberList
, SVGPathElement(SVGPathElement), unSVGPathElement, noSVGPathElement, gTypeSVGPathElement
, SVGPathSeg(SVGPathSeg), unSVGPathSeg, IsSVGPathSeg, toSVGPathSeg, noSVGPathSeg, gTypeSVGPathSeg
, SVGPathSegArcAbs(SVGPathSegArcAbs), unSVGPathSegArcAbs, noSVGPathSegArcAbs, gTypeSVGPathSegArcAbs
, SVGPathSegArcRel(SVGPathSegArcRel), unSVGPathSegArcRel, noSVGPathSegArcRel, gTypeSVGPathSegArcRel
, SVGPathSegClosePath(SVGPathSegClosePath), unSVGPathSegClosePath, noSVGPathSegClosePath, gTypeSVGPathSegClosePath
, SVGPathSegCurvetoCubicAbs(SVGPathSegCurvetoCubicAbs), unSVGPathSegCurvetoCubicAbs, noSVGPathSegCurvetoCubicAbs, gTypeSVGPathSegCurvetoCubicAbs
, SVGPathSegCurvetoCubicRel(SVGPathSegCurvetoCubicRel), unSVGPathSegCurvetoCubicRel, noSVGPathSegCurvetoCubicRel, gTypeSVGPathSegCurvetoCubicRel
, SVGPathSegCurvetoCubicSmoothAbs(SVGPathSegCurvetoCubicSmoothAbs), unSVGPathSegCurvetoCubicSmoothAbs, noSVGPathSegCurvetoCubicSmoothAbs, gTypeSVGPathSegCurvetoCubicSmoothAbs
, SVGPathSegCurvetoCubicSmoothRel(SVGPathSegCurvetoCubicSmoothRel), unSVGPathSegCurvetoCubicSmoothRel, noSVGPathSegCurvetoCubicSmoothRel, gTypeSVGPathSegCurvetoCubicSmoothRel
, SVGPathSegCurvetoQuadraticAbs(SVGPathSegCurvetoQuadraticAbs), unSVGPathSegCurvetoQuadraticAbs, noSVGPathSegCurvetoQuadraticAbs, gTypeSVGPathSegCurvetoQuadraticAbs
, SVGPathSegCurvetoQuadraticRel(SVGPathSegCurvetoQuadraticRel), unSVGPathSegCurvetoQuadraticRel, noSVGPathSegCurvetoQuadraticRel, gTypeSVGPathSegCurvetoQuadraticRel
, SVGPathSegCurvetoQuadraticSmoothAbs(SVGPathSegCurvetoQuadraticSmoothAbs), unSVGPathSegCurvetoQuadraticSmoothAbs, noSVGPathSegCurvetoQuadraticSmoothAbs, gTypeSVGPathSegCurvetoQuadraticSmoothAbs
, SVGPathSegCurvetoQuadraticSmoothRel(SVGPathSegCurvetoQuadraticSmoothRel), unSVGPathSegCurvetoQuadraticSmoothRel, noSVGPathSegCurvetoQuadraticSmoothRel, gTypeSVGPathSegCurvetoQuadraticSmoothRel
, SVGPathSegLinetoAbs(SVGPathSegLinetoAbs), unSVGPathSegLinetoAbs, noSVGPathSegLinetoAbs, gTypeSVGPathSegLinetoAbs
, SVGPathSegLinetoHorizontalAbs(SVGPathSegLinetoHorizontalAbs), unSVGPathSegLinetoHorizontalAbs, noSVGPathSegLinetoHorizontalAbs, gTypeSVGPathSegLinetoHorizontalAbs
, SVGPathSegLinetoHorizontalRel(SVGPathSegLinetoHorizontalRel), unSVGPathSegLinetoHorizontalRel, noSVGPathSegLinetoHorizontalRel, gTypeSVGPathSegLinetoHorizontalRel
, SVGPathSegLinetoRel(SVGPathSegLinetoRel), unSVGPathSegLinetoRel, noSVGPathSegLinetoRel, gTypeSVGPathSegLinetoRel
, SVGPathSegLinetoVerticalAbs(SVGPathSegLinetoVerticalAbs), unSVGPathSegLinetoVerticalAbs, noSVGPathSegLinetoVerticalAbs, gTypeSVGPathSegLinetoVerticalAbs
, SVGPathSegLinetoVerticalRel(SVGPathSegLinetoVerticalRel), unSVGPathSegLinetoVerticalRel, noSVGPathSegLinetoVerticalRel, gTypeSVGPathSegLinetoVerticalRel
, SVGPathSegList(SVGPathSegList), unSVGPathSegList, noSVGPathSegList, gTypeSVGPathSegList
, SVGPathSegMovetoAbs(SVGPathSegMovetoAbs), unSVGPathSegMovetoAbs, noSVGPathSegMovetoAbs, gTypeSVGPathSegMovetoAbs
, SVGPathSegMovetoRel(SVGPathSegMovetoRel), unSVGPathSegMovetoRel, noSVGPathSegMovetoRel, gTypeSVGPathSegMovetoRel
, SVGPatternElement(SVGPatternElement), unSVGPatternElement, noSVGPatternElement, gTypeSVGPatternElement
, SVGPoint(SVGPoint), unSVGPoint, noSVGPoint, gTypeSVGPoint
, SVGPointList(SVGPointList), unSVGPointList, noSVGPointList, gTypeSVGPointList
, SVGPolygonElement(SVGPolygonElement), unSVGPolygonElement, noSVGPolygonElement, gTypeSVGPolygonElement
, SVGPolylineElement(SVGPolylineElement), unSVGPolylineElement, noSVGPolylineElement, gTypeSVGPolylineElement
, SVGPreserveAspectRatio(SVGPreserveAspectRatio), unSVGPreserveAspectRatio, noSVGPreserveAspectRatio, gTypeSVGPreserveAspectRatio
, SVGRadialGradientElement(SVGRadialGradientElement), unSVGRadialGradientElement, noSVGRadialGradientElement, gTypeSVGRadialGradientElement
, SVGRect(SVGRect), unSVGRect, noSVGRect, gTypeSVGRect
, SVGRectElement(SVGRectElement), unSVGRectElement, noSVGRectElement, gTypeSVGRectElement
, SVGRenderingIntent(SVGRenderingIntent), unSVGRenderingIntent, noSVGRenderingIntent, gTypeSVGRenderingIntent
, SVGSVGElement(SVGSVGElement), unSVGSVGElement, noSVGSVGElement, gTypeSVGSVGElement
, SVGScriptElement(SVGScriptElement), unSVGScriptElement, noSVGScriptElement, gTypeSVGScriptElement
, SVGSetElement(SVGSetElement), unSVGSetElement, noSVGSetElement, gTypeSVGSetElement
, SVGStopElement(SVGStopElement), unSVGStopElement, noSVGStopElement, gTypeSVGStopElement
, SVGStringList(SVGStringList), unSVGStringList, noSVGStringList, gTypeSVGStringList
, SVGStyleElement(SVGStyleElement), unSVGStyleElement, noSVGStyleElement, gTypeSVGStyleElement
, SVGSwitchElement(SVGSwitchElement), unSVGSwitchElement, noSVGSwitchElement, gTypeSVGSwitchElement
, SVGSymbolElement(SVGSymbolElement), unSVGSymbolElement, noSVGSymbolElement, gTypeSVGSymbolElement
, SVGTRefElement(SVGTRefElement), unSVGTRefElement, noSVGTRefElement, gTypeSVGTRefElement
, SVGTSpanElement(SVGTSpanElement), unSVGTSpanElement, noSVGTSpanElement, gTypeSVGTSpanElement
, SVGTests(SVGTests), unSVGTests, IsSVGTests, toSVGTests, noSVGTests, gTypeSVGTests
, SVGTextContentElement(SVGTextContentElement), unSVGTextContentElement, IsSVGTextContentElement, toSVGTextContentElement, noSVGTextContentElement, gTypeSVGTextContentElement
, SVGTextElement(SVGTextElement), unSVGTextElement, noSVGTextElement, gTypeSVGTextElement
, SVGTextPathElement(SVGTextPathElement), unSVGTextPathElement, noSVGTextPathElement, gTypeSVGTextPathElement
, SVGTextPositioningElement(SVGTextPositioningElement), unSVGTextPositioningElement, IsSVGTextPositioningElement, toSVGTextPositioningElement, noSVGTextPositioningElement, gTypeSVGTextPositioningElement
, SVGTitleElement(SVGTitleElement), unSVGTitleElement, noSVGTitleElement, gTypeSVGTitleElement
, SVGTransform(SVGTransform), unSVGTransform, noSVGTransform, gTypeSVGTransform
, SVGTransformList(SVGTransformList), unSVGTransformList, noSVGTransformList, gTypeSVGTransformList
, SVGURIReference(SVGURIReference), unSVGURIReference, IsSVGURIReference, toSVGURIReference, noSVGURIReference, gTypeSVGURIReference
, SVGUnitTypes(SVGUnitTypes), unSVGUnitTypes, noSVGUnitTypes, gTypeSVGUnitTypes
, SVGUseElement(SVGUseElement), unSVGUseElement, noSVGUseElement, gTypeSVGUseElement
, SVGVKernElement(SVGVKernElement), unSVGVKernElement, noSVGVKernElement, gTypeSVGVKernElement
, SVGViewElement(SVGViewElement), unSVGViewElement, noSVGViewElement, gTypeSVGViewElement
, SVGViewSpec(SVGViewSpec), unSVGViewSpec, noSVGViewSpec, gTypeSVGViewSpec
, SVGZoomAndPan(SVGZoomAndPan), unSVGZoomAndPan, IsSVGZoomAndPan, toSVGZoomAndPan, noSVGZoomAndPan, gTypeSVGZoomAndPan
, SVGZoomEvent(SVGZoomEvent), unSVGZoomEvent, noSVGZoomEvent, gTypeSVGZoomEvent
, Screen(Screen), unScreen, noScreen, gTypeScreen
, ScriptProcessorNode(ScriptProcessorNode), unScriptProcessorNode, noScriptProcessorNode, gTypeScriptProcessorNode
, ScrollToOptions(ScrollToOptions), unScrollToOptions, noScrollToOptions, gTypeScrollToOptions
, SecurityPolicyViolationEvent(SecurityPolicyViolationEvent), unSecurityPolicyViolationEvent, noSecurityPolicyViolationEvent, gTypeSecurityPolicyViolationEvent
, SecurityPolicyViolationEventInit(SecurityPolicyViolationEventInit), unSecurityPolicyViolationEventInit, noSecurityPolicyViolationEventInit, gTypeSecurityPolicyViolationEventInit
, Selection(Selection), unSelection, noSelection, gTypeSelection
, ShadowRoot(ShadowRoot), unShadowRoot, noShadowRoot, gTypeShadowRoot
, ShadowRootInit(ShadowRootInit), unShadowRootInit, noShadowRootInit, gTypeShadowRootInit
, SiteBoundCredential(SiteBoundCredential), unSiteBoundCredential, IsSiteBoundCredential, toSiteBoundCredential, noSiteBoundCredential, gTypeSiteBoundCredential
, SiteBoundCredentialData(SiteBoundCredentialData), unSiteBoundCredentialData, IsSiteBoundCredentialData, toSiteBoundCredentialData, noSiteBoundCredentialData, gTypeSiteBoundCredentialData
, Slotable(Slotable), unSlotable, IsSlotable, toSlotable, noSlotable, gTypeSlotable
, SourceBuffer(SourceBuffer), unSourceBuffer, noSourceBuffer, gTypeSourceBuffer
, SourceBufferList(SourceBufferList), unSourceBufferList, noSourceBufferList, gTypeSourceBufferList
, SpeechSynthesis(SpeechSynthesis), unSpeechSynthesis, noSpeechSynthesis, gTypeSpeechSynthesis
, SpeechSynthesisEvent(SpeechSynthesisEvent), unSpeechSynthesisEvent, noSpeechSynthesisEvent, gTypeSpeechSynthesisEvent
, SpeechSynthesisUtterance(SpeechSynthesisUtterance), unSpeechSynthesisUtterance, noSpeechSynthesisUtterance, gTypeSpeechSynthesisUtterance
, SpeechSynthesisVoice(SpeechSynthesisVoice), unSpeechSynthesisVoice, noSpeechSynthesisVoice, gTypeSpeechSynthesisVoice
, StaticRange(StaticRange), unStaticRange, noStaticRange, gTypeStaticRange
, Storage(Storage), unStorage, noStorage, gTypeStorage
, StorageEvent(StorageEvent), unStorageEvent, noStorageEvent, gTypeStorageEvent
, StorageEventInit(StorageEventInit), unStorageEventInit, noStorageEventInit, gTypeStorageEventInit
, StorageInfo(StorageInfo), unStorageInfo, noStorageInfo, gTypeStorageInfo
, StorageQuota(StorageQuota), unStorageQuota, noStorageQuota, gTypeStorageQuota
, StyleMedia(StyleMedia), unStyleMedia, noStyleMedia, gTypeStyleMedia
, StyleSheet(StyleSheet), unStyleSheet, IsStyleSheet, toStyleSheet, noStyleSheet, gTypeStyleSheet
, StyleSheetList(StyleSheetList), unStyleSheetList, noStyleSheetList, gTypeStyleSheetList
, SubtleCrypto(SubtleCrypto), unSubtleCrypto, noSubtleCrypto, gTypeSubtleCrypto
, Text(Text), unText, IsText, toText, noText, gTypeText
, TextDecodeOptions(TextDecodeOptions), unTextDecodeOptions, noTextDecodeOptions, gTypeTextDecodeOptions
, TextDecoder(TextDecoder), unTextDecoder, noTextDecoder, gTypeTextDecoder
, TextDecoderOptions(TextDecoderOptions), unTextDecoderOptions, noTextDecoderOptions, gTypeTextDecoderOptions
, TextEncoder(TextEncoder), unTextEncoder, noTextEncoder, gTypeTextEncoder
, TextEvent(TextEvent), unTextEvent, noTextEvent, gTypeTextEvent
, TextMetrics(TextMetrics), unTextMetrics, noTextMetrics, gTypeTextMetrics
, TextTrack(TextTrack), unTextTrack, noTextTrack, gTypeTextTrack
, TextTrackCue(TextTrackCue), unTextTrackCue, IsTextTrackCue, toTextTrackCue, noTextTrackCue, gTypeTextTrackCue
, TextTrackCueList(TextTrackCueList), unTextTrackCueList, noTextTrackCueList, gTypeTextTrackCueList
, TextTrackList(TextTrackList), unTextTrackList, noTextTrackList, gTypeTextTrackList
, TimeRanges(TimeRanges), unTimeRanges, noTimeRanges, gTypeTimeRanges
, Touch(Touch), unTouch, noTouch, gTypeTouch
, TouchEvent(TouchEvent), unTouchEvent, noTouchEvent, gTypeTouchEvent
, TouchEventInit(TouchEventInit), unTouchEventInit, noTouchEventInit, gTypeTouchEventInit
, TouchList(TouchList), unTouchList, noTouchList, gTypeTouchList
, TrackEvent(TrackEvent), unTrackEvent, noTrackEvent, gTypeTrackEvent
, TrackEventInit(TrackEventInit), unTrackEventInit, noTrackEventInit, gTypeTrackEventInit
, TransitionEvent(TransitionEvent), unTransitionEvent, noTransitionEvent, gTypeTransitionEvent
, TransitionEventInit(TransitionEventInit), unTransitionEventInit, noTransitionEventInit, gTypeTransitionEventInit
, TreeWalker(TreeWalker), unTreeWalker, noTreeWalker, gTypeTreeWalker
, UIEvent(UIEvent), unUIEvent, IsUIEvent, toUIEvent, noUIEvent, gTypeUIEvent
, UIEventInit(UIEventInit), unUIEventInit, IsUIEventInit, toUIEventInit, noUIEventInit, gTypeUIEventInit
, URL(URL), unURL, noURL, gTypeURL
, URLSearchParams(URLSearchParams), unURLSearchParams, noURLSearchParams, gTypeURLSearchParams
, UserMessageHandler(UserMessageHandler), unUserMessageHandler, noUserMessageHandler, gTypeUserMessageHandler
, UserMessageHandlersNamespace(UserMessageHandlersNamespace), unUserMessageHandlersNamespace, noUserMessageHandlersNamespace, gTypeUserMessageHandlersNamespace
, VTTCue(VTTCue), unVTTCue, noVTTCue, gTypeVTTCue
, VTTRegion(VTTRegion), unVTTRegion, noVTTRegion, gTypeVTTRegion
, VTTRegionList(VTTRegionList), unVTTRegionList, noVTTRegionList, gTypeVTTRegionList
, ValidityState(ValidityState), unValidityState, noValidityState, gTypeValidityState
, VideoPlaybackQuality(VideoPlaybackQuality), unVideoPlaybackQuality, noVideoPlaybackQuality, gTypeVideoPlaybackQuality
, VideoTrack(VideoTrack), unVideoTrack, noVideoTrack, gTypeVideoTrack
, VideoTrackList(VideoTrackList), unVideoTrackList, noVideoTrackList, gTypeVideoTrackList
, WaveShaperNode(WaveShaperNode), unWaveShaperNode, noWaveShaperNode, gTypeWaveShaperNode
, WebGL2RenderingContext(WebGL2RenderingContext), unWebGL2RenderingContext, noWebGL2RenderingContext, gTypeWebGL2RenderingContext
, WebGLActiveInfo(WebGLActiveInfo), unWebGLActiveInfo, noWebGLActiveInfo, gTypeWebGLActiveInfo
, WebGLBuffer(WebGLBuffer), unWebGLBuffer, noWebGLBuffer, gTypeWebGLBuffer
, WebGLCompressedTextureATC(WebGLCompressedTextureATC), unWebGLCompressedTextureATC, noWebGLCompressedTextureATC, gTypeWebGLCompressedTextureATC
, WebGLCompressedTexturePVRTC(WebGLCompressedTexturePVRTC), unWebGLCompressedTexturePVRTC, noWebGLCompressedTexturePVRTC, gTypeWebGLCompressedTexturePVRTC
, WebGLCompressedTextureS3TC(WebGLCompressedTextureS3TC), unWebGLCompressedTextureS3TC, noWebGLCompressedTextureS3TC, gTypeWebGLCompressedTextureS3TC
, WebGLContextAttributes(WebGLContextAttributes), unWebGLContextAttributes, noWebGLContextAttributes, gTypeWebGLContextAttributes
, WebGLContextEvent(WebGLContextEvent), unWebGLContextEvent, noWebGLContextEvent, gTypeWebGLContextEvent
, WebGLContextEventInit(WebGLContextEventInit), unWebGLContextEventInit, noWebGLContextEventInit, gTypeWebGLContextEventInit
, WebGLDebugRendererInfo(WebGLDebugRendererInfo), unWebGLDebugRendererInfo, noWebGLDebugRendererInfo, gTypeWebGLDebugRendererInfo
, WebGLDebugShaders(WebGLDebugShaders), unWebGLDebugShaders, noWebGLDebugShaders, gTypeWebGLDebugShaders
, WebGLDepthTexture(WebGLDepthTexture), unWebGLDepthTexture, noWebGLDepthTexture, gTypeWebGLDepthTexture
, WebGLDrawBuffers(WebGLDrawBuffers), unWebGLDrawBuffers, noWebGLDrawBuffers, gTypeWebGLDrawBuffers
, WebGLFramebuffer(WebGLFramebuffer), unWebGLFramebuffer, noWebGLFramebuffer, gTypeWebGLFramebuffer
, WebGLLoseContext(WebGLLoseContext), unWebGLLoseContext, noWebGLLoseContext, gTypeWebGLLoseContext
, WebGLProgram(WebGLProgram), unWebGLProgram, noWebGLProgram, gTypeWebGLProgram
, WebGLQuery(WebGLQuery), unWebGLQuery, noWebGLQuery, gTypeWebGLQuery
, WebGLRenderbuffer(WebGLRenderbuffer), unWebGLRenderbuffer, noWebGLRenderbuffer, gTypeWebGLRenderbuffer
, WebGLRenderingContext(WebGLRenderingContext), unWebGLRenderingContext, noWebGLRenderingContext, gTypeWebGLRenderingContext
, WebGLRenderingContextBase(WebGLRenderingContextBase), unWebGLRenderingContextBase, IsWebGLRenderingContextBase, toWebGLRenderingContextBase, noWebGLRenderingContextBase, gTypeWebGLRenderingContextBase
, WebGLSampler(WebGLSampler), unWebGLSampler, noWebGLSampler, gTypeWebGLSampler
, WebGLShader(WebGLShader), unWebGLShader, noWebGLShader, gTypeWebGLShader
, WebGLShaderPrecisionFormat(WebGLShaderPrecisionFormat), unWebGLShaderPrecisionFormat, noWebGLShaderPrecisionFormat, gTypeWebGLShaderPrecisionFormat
, WebGLSync(WebGLSync), unWebGLSync, noWebGLSync, gTypeWebGLSync
, WebGLTexture(WebGLTexture), unWebGLTexture, noWebGLTexture, gTypeWebGLTexture
, WebGLTransformFeedback(WebGLTransformFeedback), unWebGLTransformFeedback, noWebGLTransformFeedback, gTypeWebGLTransformFeedback
, WebGLUniformLocation(WebGLUniformLocation), unWebGLUniformLocation, noWebGLUniformLocation, gTypeWebGLUniformLocation
, WebGLVertexArrayObject(WebGLVertexArrayObject), unWebGLVertexArrayObject, noWebGLVertexArrayObject, gTypeWebGLVertexArrayObject
, WebGLVertexArrayObjectOES(WebGLVertexArrayObjectOES), unWebGLVertexArrayObjectOES, noWebGLVertexArrayObjectOES, gTypeWebGLVertexArrayObjectOES
, WebGPUBuffer(WebGPUBuffer), unWebGPUBuffer, noWebGPUBuffer, gTypeWebGPUBuffer
, WebGPUCommandBuffer(WebGPUCommandBuffer), unWebGPUCommandBuffer, noWebGPUCommandBuffer, gTypeWebGPUCommandBuffer
, WebGPUCommandQueue(WebGPUCommandQueue), unWebGPUCommandQueue, noWebGPUCommandQueue, gTypeWebGPUCommandQueue
, WebGPUComputeCommandEncoder(WebGPUComputeCommandEncoder), unWebGPUComputeCommandEncoder, noWebGPUComputeCommandEncoder, gTypeWebGPUComputeCommandEncoder
, WebGPUComputePipelineState(WebGPUComputePipelineState), unWebGPUComputePipelineState, noWebGPUComputePipelineState, gTypeWebGPUComputePipelineState
, WebGPUDepthStencilDescriptor(WebGPUDepthStencilDescriptor), unWebGPUDepthStencilDescriptor, noWebGPUDepthStencilDescriptor, gTypeWebGPUDepthStencilDescriptor
, WebGPUDepthStencilState(WebGPUDepthStencilState), unWebGPUDepthStencilState, noWebGPUDepthStencilState, gTypeWebGPUDepthStencilState
, WebGPUDrawable(WebGPUDrawable), unWebGPUDrawable, noWebGPUDrawable, gTypeWebGPUDrawable
, WebGPUFunction(WebGPUFunction), unWebGPUFunction, noWebGPUFunction, gTypeWebGPUFunction
, WebGPULibrary(WebGPULibrary), unWebGPULibrary, noWebGPULibrary, gTypeWebGPULibrary
, WebGPURenderCommandEncoder(WebGPURenderCommandEncoder), unWebGPURenderCommandEncoder, noWebGPURenderCommandEncoder, gTypeWebGPURenderCommandEncoder
, WebGPURenderPassAttachmentDescriptor(WebGPURenderPassAttachmentDescriptor), unWebGPURenderPassAttachmentDescriptor, IsWebGPURenderPassAttachmentDescriptor, toWebGPURenderPassAttachmentDescriptor, noWebGPURenderPassAttachmentDescriptor, gTypeWebGPURenderPassAttachmentDescriptor
, WebGPURenderPassColorAttachmentDescriptor(WebGPURenderPassColorAttachmentDescriptor), unWebGPURenderPassColorAttachmentDescriptor, noWebGPURenderPassColorAttachmentDescriptor, gTypeWebGPURenderPassColorAttachmentDescriptor
, WebGPURenderPassDepthAttachmentDescriptor(WebGPURenderPassDepthAttachmentDescriptor), unWebGPURenderPassDepthAttachmentDescriptor, noWebGPURenderPassDepthAttachmentDescriptor, gTypeWebGPURenderPassDepthAttachmentDescriptor
, WebGPURenderPassDescriptor(WebGPURenderPassDescriptor), unWebGPURenderPassDescriptor, noWebGPURenderPassDescriptor, gTypeWebGPURenderPassDescriptor
, WebGPURenderPipelineColorAttachmentDescriptor(WebGPURenderPipelineColorAttachmentDescriptor), unWebGPURenderPipelineColorAttachmentDescriptor, noWebGPURenderPipelineColorAttachmentDescriptor, gTypeWebGPURenderPipelineColorAttachmentDescriptor
, WebGPURenderPipelineDescriptor(WebGPURenderPipelineDescriptor), unWebGPURenderPipelineDescriptor, noWebGPURenderPipelineDescriptor, gTypeWebGPURenderPipelineDescriptor
, WebGPURenderPipelineState(WebGPURenderPipelineState), unWebGPURenderPipelineState, noWebGPURenderPipelineState, gTypeWebGPURenderPipelineState
, WebGPURenderingContext(WebGPURenderingContext), unWebGPURenderingContext, noWebGPURenderingContext, gTypeWebGPURenderingContext
, WebGPUSize(WebGPUSize), unWebGPUSize, noWebGPUSize, gTypeWebGPUSize
, WebGPUTexture(WebGPUTexture), unWebGPUTexture, noWebGPUTexture, gTypeWebGPUTexture
, WebGPUTextureDescriptor(WebGPUTextureDescriptor), unWebGPUTextureDescriptor, noWebGPUTextureDescriptor, gTypeWebGPUTextureDescriptor
, WebKitAnimationEvent(WebKitAnimationEvent), unWebKitAnimationEvent, noWebKitAnimationEvent, gTypeWebKitAnimationEvent
, WebKitAnimationEventInit(WebKitAnimationEventInit), unWebKitAnimationEventInit, noWebKitAnimationEventInit, gTypeWebKitAnimationEventInit
, WebKitCSSMatrix(WebKitCSSMatrix), unWebKitCSSMatrix, noWebKitCSSMatrix, gTypeWebKitCSSMatrix
, WebKitCSSRegionRule(WebKitCSSRegionRule), unWebKitCSSRegionRule, noWebKitCSSRegionRule, gTypeWebKitCSSRegionRule
, WebKitCSSViewportRule(WebKitCSSViewportRule), unWebKitCSSViewportRule, noWebKitCSSViewportRule, gTypeWebKitCSSViewportRule
, WebKitMediaKeyError(WebKitMediaKeyError), unWebKitMediaKeyError, noWebKitMediaKeyError, gTypeWebKitMediaKeyError
, WebKitMediaKeyMessageEvent(WebKitMediaKeyMessageEvent), unWebKitMediaKeyMessageEvent, noWebKitMediaKeyMessageEvent, gTypeWebKitMediaKeyMessageEvent
, WebKitMediaKeyMessageEventInit(WebKitMediaKeyMessageEventInit), unWebKitMediaKeyMessageEventInit, noWebKitMediaKeyMessageEventInit, gTypeWebKitMediaKeyMessageEventInit
, WebKitMediaKeyNeededEvent(WebKitMediaKeyNeededEvent), unWebKitMediaKeyNeededEvent, noWebKitMediaKeyNeededEvent, gTypeWebKitMediaKeyNeededEvent
, WebKitMediaKeyNeededEventInit(WebKitMediaKeyNeededEventInit), unWebKitMediaKeyNeededEventInit, noWebKitMediaKeyNeededEventInit, gTypeWebKitMediaKeyNeededEventInit
, WebKitMediaKeySession(WebKitMediaKeySession), unWebKitMediaKeySession, noWebKitMediaKeySession, gTypeWebKitMediaKeySession
, WebKitMediaKeys(WebKitMediaKeys), unWebKitMediaKeys, noWebKitMediaKeys, gTypeWebKitMediaKeys
, WebKitNamedFlow(WebKitNamedFlow), unWebKitNamedFlow, noWebKitNamedFlow, gTypeWebKitNamedFlow
, WebKitNamespace(WebKitNamespace), unWebKitNamespace, noWebKitNamespace, gTypeWebKitNamespace
, WebKitPlaybackTargetAvailabilityEvent(WebKitPlaybackTargetAvailabilityEvent), unWebKitPlaybackTargetAvailabilityEvent, noWebKitPlaybackTargetAvailabilityEvent, gTypeWebKitPlaybackTargetAvailabilityEvent
, WebKitPlaybackTargetAvailabilityEventInit(WebKitPlaybackTargetAvailabilityEventInit), unWebKitPlaybackTargetAvailabilityEventInit, noWebKitPlaybackTargetAvailabilityEventInit, gTypeWebKitPlaybackTargetAvailabilityEventInit
, WebKitPoint(WebKitPoint), unWebKitPoint, noWebKitPoint, gTypeWebKitPoint
, WebKitSubtleCrypto(WebKitSubtleCrypto), unWebKitSubtleCrypto, noWebKitSubtleCrypto, gTypeWebKitSubtleCrypto
, WebKitTransitionEvent(WebKitTransitionEvent), unWebKitTransitionEvent, noWebKitTransitionEvent, gTypeWebKitTransitionEvent
, WebKitTransitionEventInit(WebKitTransitionEventInit), unWebKitTransitionEventInit, noWebKitTransitionEventInit, gTypeWebKitTransitionEventInit
, WebSocket(WebSocket), unWebSocket, noWebSocket, gTypeWebSocket
, WheelEvent(WheelEvent), unWheelEvent, noWheelEvent, gTypeWheelEvent
, WheelEventInit(WheelEventInit), unWheelEventInit, noWheelEventInit, gTypeWheelEventInit
, Window(Window), unWindow, noWindow, gTypeWindow
, WindowEventHandlers(WindowEventHandlers), unWindowEventHandlers, IsWindowEventHandlers, toWindowEventHandlers, noWindowEventHandlers, gTypeWindowEventHandlers
, WindowOrWorkerGlobalScope(WindowOrWorkerGlobalScope), unWindowOrWorkerGlobalScope, IsWindowOrWorkerGlobalScope, toWindowOrWorkerGlobalScope, noWindowOrWorkerGlobalScope, gTypeWindowOrWorkerGlobalScope
, Worker(Worker), unWorker, noWorker, gTypeWorker
, WorkerGlobalScope(WorkerGlobalScope), unWorkerGlobalScope, IsWorkerGlobalScope, toWorkerGlobalScope, noWorkerGlobalScope, gTypeWorkerGlobalScope
, WorkerLocation(WorkerLocation), unWorkerLocation, noWorkerLocation, gTypeWorkerLocation
, WorkerNavigator(WorkerNavigator), unWorkerNavigator, noWorkerNavigator, gTypeWorkerNavigator
, WritableStream(WritableStream), unWritableStream, noWritableStream, gTypeWritableStream
, XMLDocument(XMLDocument), unXMLDocument, noXMLDocument, gTypeXMLDocument
, XMLHttpRequest(XMLHttpRequest), unXMLHttpRequest, noXMLHttpRequest, gTypeXMLHttpRequest
, XMLHttpRequestEventTarget(XMLHttpRequestEventTarget), unXMLHttpRequestEventTarget, IsXMLHttpRequestEventTarget, toXMLHttpRequestEventTarget, noXMLHttpRequestEventTarget, gTypeXMLHttpRequestEventTarget
, XMLHttpRequestProgressEvent(XMLHttpRequestProgressEvent), unXMLHttpRequestProgressEvent, noXMLHttpRequestProgressEvent, gTypeXMLHttpRequestProgressEvent
, XMLHttpRequestUpload(XMLHttpRequestUpload), unXMLHttpRequestUpload, noXMLHttpRequestUpload, gTypeXMLHttpRequestUpload
, XMLSerializer(XMLSerializer), unXMLSerializer, noXMLSerializer, gTypeXMLSerializer
, XPathEvaluator(XPathEvaluator), unXPathEvaluator, noXPathEvaluator, gTypeXPathEvaluator
, XPathException(XPathException), unXPathException, noXPathException, gTypeXPathException
, XPathExpression(XPathExpression), unXPathExpression, noXPathExpression, gTypeXPathExpression
, XPathNSResolver(XPathNSResolver), unXPathNSResolver, noXPathNSResolver, gTypeXPathNSResolver
, XPathResult(XPathResult), unXPathResult, noXPathResult, gTypeXPathResult
, XSLTProcessor(XSLTProcessor), unXSLTProcessor, noXSLTProcessor, gTypeXSLTProcessor
) where
import Prelude ()
import Prelude.Compat hiding((!!))
import qualified Data.Text as T (unpack, Text)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Word (Word8, Word16, Word32, Word64)
import GHCJS.Marshal (ToJSVal(..), FromJSVal(..))
import GHCJS.Marshal.Pure (PToJSVal(..), PFromJSVal(..))
import Language.Javascript.JSaddle
(Object(..), valToBool, valNull, valToNumber, (!!), js, valToText,
JSVal, JSString, JSM, maybeNullOrUndefined, maybeNullOrUndefined',
valToStr, jsg, ToJSString(..), FromJSString(..), strToText, MakeObject(..),
Nullable(..), freeFunction, instanceOf, JSContextRef,
askJSM, runJSM, MonadJSM(..), liftJSM, strictEqual, function, js2)
import qualified Language.Javascript.JSaddle as JSaddle (Function(..))
import Foreign.Ptr (nullPtr)
import Control.Lens.Operators ((^.))
import Data.Maybe (catMaybes)
import Language.Javascript.JSaddle.Classes (ToJSVal(..))
import Control.Monad ((>=>))
import Control.Concurrent.MVar (newEmptyMVar, putMVar, takeMVar)
import Data.Coerce (coerce, Coercible)
import Data.Typeable (Typeable)
import Control.Monad.Trans.Reader (ReaderT(..), ask)
import Control.Exception (bracket, Exception(..), throwIO)
#if MIN_VERSION_base(4,9,0)
import GHC.Stack (HasCallStack)
#else
import GHC.Exts (Constraint)
type HasCallStack = (() :: Constraint)
#endif
type DOM = JSM
type DOMContext = JSContextRef
type MonadDOM = MonadJSM
liftDOM :: MonadDOM m => DOM a -> m a
liftDOM = liftJSM
askDOM :: MonadDOM m => m DOMContext
askDOM = askJSM
runDOM :: MonadIO m => DOM a -> DOMContext -> m a
runDOM = runJSM
newtype GType = GType Object
typeInstanceIsA :: ToJSVal value => value -> GType -> JSM Bool
typeInstanceIsA o (GType t) = o `instanceOf` t
castTo :: forall obj obj' m. (Coercible obj JSVal, IsGObject obj', MonadJSM m) => (JSVal -> obj') -> obj -> m (Maybe obj')
castTo constructor obj = liftJSM $ do
GType gtype <- typeGType (undefined :: obj')
let jsval = coerce obj
jsval `instanceOf` gtype >>= \case
True -> return . Just $ constructor jsval
False -> return Nothing
unsafeCastTo :: forall obj obj' m. (HasCallStack, Coercible obj JSVal, IsGObject obj', MonadJSM m) => (JSVal -> obj') -> obj -> m obj'
unsafeCastTo constructor obj = liftJSM $ do
GType gtype <- typeGType (undefined :: obj')
let jsval = coerce obj
jsval `instanceOf` gtype >>= \case
True -> return $ constructor jsval
False -> do
destType <- valToText (gtype ^. js "name")
error $ "unsafeCastTo :: invalid conversion to "
<> T.unpack destType <> " requested."
uncheckedCastTo :: (Coercible obj JSVal, IsGObject obj') => (JSVal -> obj') -> obj -> obj'
uncheckedCastTo constructor = constructor . coerce
isA :: IsGObject o => o -> GType -> JSM Bool
isA obj = typeInstanceIsA (unGObject $ toGObject obj)
newtype GObject = GObject { unGObject :: JSVal }
noGObject :: Maybe GObject
noGObject = Nothing
{-# INLINE noGObject #-}
class (ToJSVal o, FromJSVal o, Coercible o JSVal) => IsGObject o where
typeGType :: o -> JSM GType
toGObject :: IsGObject o => o -> GObject
toGObject = GObject . coerce
fromJSArray :: FromJSVal o => JSVal -> JSM [Maybe o]
fromJSArray a = do
l <- a ^. js "length" >>= valToNumber
mapM (\i -> a !! i >>= fromJSVal) [0..round l - 1]
fromJSArrayUnchecked :: FromJSVal o => JSVal -> JSM [o]
fromJSArrayUnchecked = fromJSValUncheckedListOf
nullableToMaybe :: FromJSVal a => JSVal -> JSM (Maybe a)
nullableToMaybe = fromJSVal
{-# INLINE nullableToMaybe #-}
maybeToNullable :: ToJSVal a => Maybe a -> JSM JSVal
maybeToNullable Nothing = return valNull
maybeToNullable (Just a) = toJSVal a
{-# INLINE maybeToNullable #-}
instance PToJSVal GObject where
pToJSVal = unGObject
{-# INLINE pToJSVal #-}
instance PFromJSVal GObject where
pFromJSVal = GObject
{-# INLINE pFromJSVal #-}
instance ToJSVal GObject where
toJSVal = return . unGObject
{-# INLINE toJSVal #-}
instance FromJSVal GObject where
fromJSVal val = fmap GObject <$> maybeNullOrUndefined val
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . GObject
{-# INLINE fromJSValUnchecked #-}
instance IsGObject GObject where
typeGType _ = gTypeGObject
{-# INLINE typeGType #-}
#ifdef ghcjs_HOST_OS
foreign import javascript unsafe "Object" gTypeGObject :: IO GType
#else
gTypeGObject :: JSM GType
gTypeGObject = GType . Object <$> jsg "Object"
#endif
objectToString :: (IsGObject self, FromJSString result) => self -> JSM result
objectToString self = fromJSValUnchecked (unGObject $ toGObject self)
type DOMString = JSString
noDOMString :: Maybe DOMString
noDOMString = Nothing
{-# INLINE noDOMString #-}
type CSSOMString = JSString
noCSSOMString :: Maybe CSSOMString
noCSSOMString = Nothing
{-# INLINE noCSSOMString #-}
type USVString = JSString
noUSVString :: Maybe USVString
noUSVString = Nothing
{-# INLINE noUSVString #-}
type ByteString = JSString
noByteString :: Maybe ByteString
noByteString = Nothing
{-# INLINE noByteString #-}
fromJSStringArray :: FromJSString s => JSVal -> JSM [s]
fromJSStringArray a = do
l <- a ^. js "length" >>= valToNumber
mapM (\i -> fromJSString <$> (a !! i >>= valToStr)) [0..round l - 1]
toMaybeJSString :: ToJSString a => Maybe a -> JSM JSVal
toMaybeJSString Nothing = return valNull
toMaybeJSString (Just a) = toJSVal (toJSString a)
{-# INLINE toMaybeJSString #-}
fromMaybeJSString :: FromJSString a => JSVal -> JSM (Maybe a)
fromMaybeJSString = maybeNullOrUndefined' (fmap fromJSString . valToStr)
{-# INLINE fromMaybeJSString #-}
integralToDoubleToJSVal :: Integral a => a -> JSM JSVal
integralToDoubleToJSVal a = toJSVal (fromIntegral a :: Double)
integralFromDoubleFromJSVal :: Integral a => JSVal -> JSM (Maybe a)
integralFromDoubleFromJSVal = fmap (fmap round) . (fromJSVal :: JSVal -> JSM (Maybe Double))
integralFromDoubleFromJSValUnchecked :: Integral a => JSVal -> JSM a
integralFromDoubleFromJSValUnchecked = fmap round . (fromJSValUnchecked :: JSVal -> JSM Double)
noJSString :: Maybe JSString
noJSString = Nothing
{-# INLINE noJSString #-}
type ToDOMString s = ToJSString s
type FromDOMString s = FromJSString s
type IsDOMString s = (ToDOMString s, FromDOMString s)
type IsCSSOMString s = (ToDOMString s, FromDOMString s)
type IsUSVString s = (ToDOMString s, FromDOMString s)
type IsByteString s = (ToDOMString s, FromDOMString s)
newtype RawTypedArray = RawTypedArray { unRawTypedArray :: JSVal }
noRawTypedArray :: Maybe RawTypedArray
noRawTypedArray = Nothing
{-# INLINE noRawTypedArray #-}
instance PToJSVal RawTypedArray where
pToJSVal = unRawTypedArray
{-# INLINE pToJSVal #-}
instance PFromJSVal RawTypedArray where
pFromJSVal = RawTypedArray
{-# INLINE pFromJSVal #-}
instance ToJSVal RawTypedArray where
toJSVal = return . unRawTypedArray
{-# INLINE toJSVal #-}
instance FromJSVal RawTypedArray where
fromJSVal v = fmap RawTypedArray <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RawTypedArray
{-# INLINE fromJSValUnchecked #-}
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRawTypedArray o
toRawTypedArray :: IsRawTypedArray o => o -> RawTypedArray
toRawTypedArray = RawTypedArray . coerce
newtype Function = Function { unFunction :: JSVal }
noFunction :: Maybe Function
noFunction = Nothing
{-# INLINE noFunction #-}
instance PToJSVal Function where
pToJSVal = unFunction
{-# INLINE pToJSVal #-}
instance PFromJSVal Function where
pFromJSVal = Function
{-# INLINE pFromJSVal #-}
instance ToJSVal Function where
toJSVal = return . unFunction
{-# INLINE toJSVal #-}
instance FromJSVal Function where
fromJSVal v = fmap Function <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Function
{-# INLINE fromJSValUnchecked #-}
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsFunction o
toFunction :: IsFunction o => o -> Function
toFunction = Function . coerce
instance IsFunction Function
newtype PromiseRejected = PromiseRejected { rejectionReason :: JSVal } deriving (Typeable)
noPromiseRejected :: Maybe PromiseRejected
noPromiseRejected = Nothing
{-# INLINE noPromiseRejected #-}
instance Show PromiseRejected where
show _ = "A promise was rejected"
instance Exception PromiseRejected
readPromise :: JSVal -> JSM JSVal
readPromise promise = do
resultMVar <- liftIO newEmptyMVar
success <- function (\_ _ [result] -> liftIO . putMVar resultMVar $ Right result)
error <- function (\_ _ [reason] -> liftIO . putMVar resultMVar $ Left reason)
promise ^. js2 "then" success error
result <- liftIO $ takeMVar resultMVar
freeFunction success
freeFunction error
case result of
Left reason -> liftIO . throwIO $ PromiseRejected reason
Right x -> return x
newtype Callback a = Callback JSaddle.Function
withCallback :: (MonadDOM m, Coercible c JSaddle.Function)
=> JSM c -> (c -> JSM a) -> m a
withCallback aquire f = do
jsCtx <- askJSM
liftIO $ bracket
(runJSM aquire jsCtx)
((`runJSM` jsCtx) . freeFunction . coerce)
(\t -> runJSM (f t) jsCtx)
newtype AudioBufferCallback = AudioBufferCallback (Callback (JSVal -> IO ()))
noAudioBufferCallback :: Maybe AudioBufferCallback
noAudioBufferCallback = Nothing
{-# INLINE noAudioBufferCallback #-}
instance ToJSVal AudioBufferCallback where toJSVal (AudioBufferCallback (Callback r)) = toJSVal r
newtype BlobCallback = BlobCallback (Callback (JSVal -> IO ()))
noBlobCallback :: Maybe BlobCallback
noBlobCallback = Nothing
{-# INLINE noBlobCallback #-}
instance ToJSVal BlobCallback where toJSVal (BlobCallback (Callback r)) = toJSVal r
newtype DatabaseCallback = DatabaseCallback (Callback (JSVal -> IO ()))
noDatabaseCallback :: Maybe DatabaseCallback
noDatabaseCallback = Nothing
{-# INLINE noDatabaseCallback #-}
instance ToJSVal DatabaseCallback where toJSVal (DatabaseCallback (Callback r)) = toJSVal r
newtype IntersectionObserverCallback = IntersectionObserverCallback (Callback (JSVal -> JSVal -> IO ()))
noIntersectionObserverCallback :: Maybe IntersectionObserverCallback
noIntersectionObserverCallback = Nothing
{-# INLINE noIntersectionObserverCallback #-}
instance ToJSVal IntersectionObserverCallback where toJSVal (IntersectionObserverCallback (Callback r)) = toJSVal r
newtype MediaQueryListListener = MediaQueryListListener (Callback (JSVal -> IO ()))
noMediaQueryListListener :: Maybe MediaQueryListListener
noMediaQueryListListener = Nothing
{-# INLINE noMediaQueryListListener #-}
instance ToJSVal MediaQueryListListener where toJSVal (MediaQueryListListener (Callback r)) = toJSVal r
newtype MediaStreamTrackSourcesCallback = MediaStreamTrackSourcesCallback (Callback (JSVal -> IO ()))
noMediaStreamTrackSourcesCallback :: Maybe MediaStreamTrackSourcesCallback
noMediaStreamTrackSourcesCallback = Nothing
{-# INLINE noMediaStreamTrackSourcesCallback #-}
instance ToJSVal MediaStreamTrackSourcesCallback where toJSVal (MediaStreamTrackSourcesCallback (Callback r)) = toJSVal r
newtype NavigatorUserMediaErrorCallback = NavigatorUserMediaErrorCallback (Callback (JSVal -> IO ()))
noNavigatorUserMediaErrorCallback :: Maybe NavigatorUserMediaErrorCallback
noNavigatorUserMediaErrorCallback = Nothing
{-# INLINE noNavigatorUserMediaErrorCallback #-}
instance ToJSVal NavigatorUserMediaErrorCallback where toJSVal (NavigatorUserMediaErrorCallback (Callback r)) = toJSVal r
newtype NavigatorUserMediaSuccessCallback = NavigatorUserMediaSuccessCallback (Callback (JSVal -> IO ()))
noNavigatorUserMediaSuccessCallback :: Maybe NavigatorUserMediaSuccessCallback
noNavigatorUserMediaSuccessCallback = Nothing
{-# INLINE noNavigatorUserMediaSuccessCallback #-}
instance ToJSVal NavigatorUserMediaSuccessCallback where toJSVal (NavigatorUserMediaSuccessCallback (Callback r)) = toJSVal r
newtype NotificationPermissionCallback permissions = NotificationPermissionCallback (Callback (JSVal -> IO ()))
instance ToJSVal (NotificationPermissionCallback permissions) where toJSVal (NotificationPermissionCallback (Callback r)) = toJSVal r
newtype NodeFilter = NodeFilter (Callback (JSVal -> IO ()))
noNodeFilter :: Maybe NodeFilter
noNodeFilter = Nothing
{-# INLINE noNodeFilter #-}
instance ToJSVal NodeFilter where toJSVal (NodeFilter (Callback r)) = toJSVal r
newtype PositionCallback = PositionCallback (Callback (JSVal -> IO ()))
noPositionCallback :: Maybe PositionCallback
noPositionCallback = Nothing
{-# INLINE noPositionCallback #-}
instance ToJSVal PositionCallback where toJSVal (PositionCallback (Callback r)) = toJSVal r
newtype PositionErrorCallback = PositionErrorCallback (Callback (JSVal -> IO ()))
noPositionErrorCallback :: Maybe PositionErrorCallback
noPositionErrorCallback = Nothing
{-# INLINE noPositionErrorCallback #-}
instance ToJSVal PositionErrorCallback where toJSVal (PositionErrorCallback (Callback r)) = toJSVal r
newtype PerformanceObserverCallback = PerformanceObserverCallback (Callback (JSVal -> JSVal -> IO ()))
noPerformanceObserverCallback :: Maybe PerformanceObserverCallback
noPerformanceObserverCallback = Nothing
{-# INLINE noPerformanceObserverCallback #-}
instance ToJSVal PerformanceObserverCallback where toJSVal (PerformanceObserverCallback (Callback r)) = toJSVal r
newtype RequestAnimationFrameCallback = RequestAnimationFrameCallback (Callback (JSVal -> IO ()))
noRequestAnimationFrameCallback :: Maybe RequestAnimationFrameCallback
noRequestAnimationFrameCallback = Nothing
{-# INLINE noRequestAnimationFrameCallback #-}
instance ToJSVal RequestAnimationFrameCallback where toJSVal (RequestAnimationFrameCallback (Callback r)) = toJSVal r
newtype RTCPeerConnectionErrorCallback = RTCPeerConnectionErrorCallback (Callback (JSVal -> IO ()))
noRTCPeerConnectionErrorCallback :: Maybe RTCPeerConnectionErrorCallback
noRTCPeerConnectionErrorCallback = Nothing
{-# INLINE noRTCPeerConnectionErrorCallback #-}
instance ToJSVal RTCPeerConnectionErrorCallback where toJSVal (RTCPeerConnectionErrorCallback (Callback r)) = toJSVal r
newtype RTCSessionDescriptionCallback = RTCSessionDescriptionCallback (Callback (JSVal -> IO ()))
noRTCSessionDescriptionCallback :: Maybe RTCSessionDescriptionCallback
noRTCSessionDescriptionCallback = Nothing
{-# INLINE noRTCSessionDescriptionCallback #-}
instance ToJSVal RTCSessionDescriptionCallback where toJSVal (RTCSessionDescriptionCallback (Callback r)) = toJSVal r
newtype RTCStatsCallback = RTCStatsCallback (Callback (JSVal -> IO ()))
noRTCStatsCallback :: Maybe RTCStatsCallback
noRTCStatsCallback = Nothing
{-# INLINE noRTCStatsCallback #-}
instance ToJSVal RTCStatsCallback where toJSVal (RTCStatsCallback (Callback r)) = toJSVal r
newtype SQLStatementCallback = SQLStatementCallback (Callback (JSVal -> JSVal -> IO ()))
noSQLStatementCallback :: Maybe SQLStatementCallback
noSQLStatementCallback = Nothing
{-# INLINE noSQLStatementCallback #-}
instance ToJSVal SQLStatementCallback where toJSVal (SQLStatementCallback (Callback r)) = toJSVal r
newtype SQLStatementErrorCallback = SQLStatementErrorCallback (Callback (JSVal -> JSVal -> IO ()))
noSQLStatementErrorCallback :: Maybe SQLStatementErrorCallback
noSQLStatementErrorCallback = Nothing
{-# INLINE noSQLStatementErrorCallback #-}
instance ToJSVal SQLStatementErrorCallback where toJSVal (SQLStatementErrorCallback (Callback r)) = toJSVal r
newtype SQLTransactionCallback = SQLTransactionCallback (Callback (JSVal -> IO ()))
noSQLTransactionCallback :: Maybe SQLTransactionCallback
noSQLTransactionCallback = Nothing
{-# INLINE noSQLTransactionCallback #-}
instance ToJSVal SQLTransactionCallback where toJSVal (SQLTransactionCallback (Callback r)) = toJSVal r
newtype SQLTransactionErrorCallback = SQLTransactionErrorCallback (Callback (JSVal -> IO ()))
noSQLTransactionErrorCallback :: Maybe SQLTransactionErrorCallback
noSQLTransactionErrorCallback = Nothing
{-# INLINE noSQLTransactionErrorCallback #-}
instance ToJSVal SQLTransactionErrorCallback where toJSVal (SQLTransactionErrorCallback (Callback r)) = toJSVal r
newtype StorageErrorCallback = StorageErrorCallback (Callback (JSVal -> IO ()))
noStorageErrorCallback :: Maybe StorageErrorCallback
noStorageErrorCallback = Nothing
{-# INLINE noStorageErrorCallback #-}
instance ToJSVal StorageErrorCallback where toJSVal (StorageErrorCallback (Callback r)) = toJSVal r
newtype StorageQuotaCallback = StorageQuotaCallback (Callback (JSVal -> IO ()))
noStorageQuotaCallback :: Maybe StorageQuotaCallback
noStorageQuotaCallback = Nothing
{-# INLINE noStorageQuotaCallback #-}
instance ToJSVal StorageQuotaCallback where toJSVal (StorageQuotaCallback (Callback r)) = toJSVal r
newtype StorageUsageCallback = StorageUsageCallback (Callback (JSVal -> JSVal -> IO ()))
noStorageUsageCallback :: Maybe StorageUsageCallback
noStorageUsageCallback = Nothing
{-# INLINE noStorageUsageCallback #-}
instance ToJSVal StorageUsageCallback where toJSVal (StorageUsageCallback (Callback r)) = toJSVal r
newtype StringCallback s = StringCallback (Callback (JSVal -> IO ()))
instance ToJSVal (StringCallback s) where toJSVal (StringCallback (Callback r)) = toJSVal r
newtype VoidCallback = VoidCallback (Callback (IO ()))
noVoidCallback :: Maybe VoidCallback
noVoidCallback = Nothing
{-# INLINE noVoidCallback #-}
instance ToJSVal VoidCallback where toJSVal (VoidCallback (Callback r)) = toJSVal r
type DOMHighResTimeStamp = Double
noDOMHighResTimeStamp :: Maybe DOMHighResTimeStamp
noDOMHighResTimeStamp = Nothing
{-# INLINE noDOMHighResTimeStamp #-}
type PerformanceEntryList = [PerformanceEntry]
noPerformanceEntryList :: Maybe PerformanceEntryList
noPerformanceEntryList = Nothing
{-# INLINE noPerformanceEntryList #-}
newtype Record key value = Record { unRecord :: JSVal }
instance PToJSVal (Record key value) where
pToJSVal = unRecord
{-# INLINE pToJSVal #-}
instance PFromJSVal (Record key value) where
pFromJSVal = Record
{-# INLINE pFromJSVal #-}
instance ToJSVal (Record key value) where
toJSVal = return . unRecord
{-# INLINE toJSVal #-}
instance FromJSVal (Record key value) where
fromJSVal v = fmap Record <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Record
{-# INLINE fromJSValUnchecked #-}
newtype SerializedScriptValue = SerializedScriptValue { unSerializedScriptValue :: JSVal }
noSerializedScriptValue :: Maybe SerializedScriptValue
noSerializedScriptValue = Nothing
{-# INLINE noSerializedScriptValue #-}
instance PToJSVal SerializedScriptValue where
pToJSVal = unSerializedScriptValue
{-# INLINE pToJSVal #-}
instance PFromJSVal SerializedScriptValue where
pFromJSVal = SerializedScriptValue
{-# INLINE pFromJSVal #-}
instance ToJSVal SerializedScriptValue where
toJSVal = return . unSerializedScriptValue
{-# INLINE toJSVal #-}
instance FromJSVal SerializedScriptValue where
fromJSVal v = fmap SerializedScriptValue <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SerializedScriptValue
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsSerializedScriptValue o
toSerializedScriptValue :: IsSerializedScriptValue o => o -> SerializedScriptValue
toSerializedScriptValue = SerializedScriptValue . coerce
instance IsSerializedScriptValue SerializedScriptValue
instance IsGObject SerializedScriptValue where
typeGType _ = error "Unable to get the JavaScript type of SerializedScriptValue"
newtype Dictionary = Dictionary { unDictionary :: JSVal }
noDictionary :: Maybe Dictionary
noDictionary = Nothing
{-# INLINE noDictionary #-}
instance PToJSVal Dictionary where
pToJSVal = unDictionary
{-# INLINE pToJSVal #-}
instance PFromJSVal Dictionary where
pFromJSVal = Dictionary
{-# INLINE pFromJSVal #-}
instance ToJSVal Dictionary where
toJSVal = return . unDictionary
{-# INLINE toJSVal #-}
instance FromJSVal Dictionary where
fromJSVal v = fmap Dictionary <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Dictionary
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsDictionary o
toDictionary :: IsDictionary o => o -> Dictionary
toDictionary = Dictionary . coerce
instance IsDictionary Dictionary
instance IsGObject Dictionary where
typeGType _ = error "Unable to get the JavaScript type of Dictionary"
newtype MutationCallback = MutationCallback { unMutationCallback :: JSVal }
noMutationCallback :: Maybe MutationCallback
noMutationCallback = Nothing
{-# INLINE noMutationCallback #-}
instance PToJSVal MutationCallback where
pToJSVal = unMutationCallback
{-# INLINE pToJSVal #-}
instance PFromJSVal MutationCallback where
pFromJSVal = MutationCallback
{-# INLINE pFromJSVal #-}
instance ToJSVal MutationCallback where
toJSVal = return . unMutationCallback
{-# INLINE toJSVal #-}
instance FromJSVal MutationCallback where
fromJSVal v = fmap MutationCallback <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MutationCallback
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsMutationCallback o
toMutationCallback :: IsMutationCallback o => o -> MutationCallback
toMutationCallback = MutationCallback . coerce
instance IsMutationCallback MutationCallback
instance IsGObject MutationCallback where
typeGType _ = error "Unable to get the JavaScript type of MutationCallback"
newtype ArrayBuffer = ArrayBuffer { unArrayBuffer :: JSVal }
noArrayBuffer :: Maybe ArrayBuffer
noArrayBuffer = Nothing
{-# INLINE noArrayBuffer #-}
instance PToJSVal ArrayBuffer where
pToJSVal = unArrayBuffer
{-# INLINE pToJSVal #-}
instance PFromJSVal ArrayBuffer where
pFromJSVal = ArrayBuffer
{-# INLINE pFromJSVal #-}
instance ToJSVal ArrayBuffer where
toJSVal = return . unArrayBuffer
{-# INLINE toJSVal #-}
instance FromJSVal ArrayBuffer where
fromJSVal v = fmap ArrayBuffer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ArrayBuffer
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsArrayBuffer o
toArrayBuffer :: IsArrayBuffer o => o -> ArrayBuffer
toArrayBuffer = ArrayBuffer . coerce
instance IsArrayBuffer ArrayBuffer
instance IsGObject ArrayBuffer where
typeGType _ = gTypeArrayBuffer
gTypeArrayBuffer :: JSM GType
gTypeArrayBuffer = GType . Object <$> jsg "ArrayBuffer"
newtype Float32Array = Float32Array { unFloat32Array :: JSVal }
noFloat32Array :: Maybe Float32Array
noFloat32Array = Nothing
{-# INLINE noFloat32Array #-}
instance PToJSVal Float32Array where
pToJSVal = unFloat32Array
{-# INLINE pToJSVal #-}
instance PFromJSVal Float32Array where
pFromJSVal = Float32Array
{-# INLINE pFromJSVal #-}
instance ToJSVal Float32Array where
toJSVal = return . unFloat32Array
{-# INLINE toJSVal #-}
instance FromJSVal Float32Array where
fromJSVal v = fmap Float32Array <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Float32Array
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsFloat32Array o
toFloat32Array :: IsFloat32Array o => o -> Float32Array
toFloat32Array = Float32Array . coerce
instance IsFloat32Array Float32Array
instance IsGObject Float32Array where
typeGType _ = gTypeFloat32Array
gTypeFloat32Array :: JSM GType
gTypeFloat32Array = GType . Object <$> jsg "Float32Array"
newtype Float64Array = Float64Array { unFloat64Array :: JSVal }
noFloat64Array :: Maybe Float64Array
noFloat64Array = Nothing
{-# INLINE noFloat64Array #-}
instance PToJSVal Float64Array where
pToJSVal = unFloat64Array
{-# INLINE pToJSVal #-}
instance PFromJSVal Float64Array where
pFromJSVal = Float64Array
{-# INLINE pFromJSVal #-}
instance ToJSVal Float64Array where
toJSVal = return . unFloat64Array
{-# INLINE toJSVal #-}
instance FromJSVal Float64Array where
fromJSVal v = fmap Float64Array <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Float64Array
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsFloat64Array o
toFloat64Array :: IsFloat64Array o => o -> Float64Array
toFloat64Array = Float64Array . coerce
instance IsFloat64Array Float64Array
instance IsGObject Float64Array where
typeGType _ = gTypeFloat64Array
gTypeFloat64Array :: JSM GType
gTypeFloat64Array = GType . Object <$> jsg "Float64Array"
newtype Uint8Array = Uint8Array { unUint8Array :: JSVal }
noUint8Array :: Maybe Uint8Array
noUint8Array = Nothing
{-# INLINE noUint8Array #-}
instance PToJSVal Uint8Array where
pToJSVal = unUint8Array
{-# INLINE pToJSVal #-}
instance PFromJSVal Uint8Array where
pFromJSVal = Uint8Array
{-# INLINE pFromJSVal #-}
instance ToJSVal Uint8Array where
toJSVal = return . unUint8Array
{-# INLINE toJSVal #-}
instance FromJSVal Uint8Array where
fromJSVal v = fmap Uint8Array <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Uint8Array
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsUint8Array o
toUint8Array :: IsUint8Array o => o -> Uint8Array
toUint8Array = Uint8Array . coerce
instance IsUint8Array Uint8Array
instance IsGObject Uint8Array where
typeGType _ = gTypeUint8Array
gTypeUint8Array :: JSM GType
gTypeUint8Array = GType . Object <$> jsg "Uint8Array"
newtype Uint8ClampedArray = Uint8ClampedArray { unUint8ClampedArray :: JSVal }
noUint8ClampedArray :: Maybe Uint8ClampedArray
noUint8ClampedArray = Nothing
{-# INLINE noUint8ClampedArray #-}
instance PToJSVal Uint8ClampedArray where
pToJSVal = unUint8ClampedArray
{-# INLINE pToJSVal #-}
instance PFromJSVal Uint8ClampedArray where
pFromJSVal = Uint8ClampedArray
{-# INLINE pFromJSVal #-}
instance ToJSVal Uint8ClampedArray where
toJSVal = return . unUint8ClampedArray
{-# INLINE toJSVal #-}
instance FromJSVal Uint8ClampedArray where
fromJSVal v = fmap Uint8ClampedArray <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Uint8ClampedArray
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsUint8ClampedArray o
toUint8ClampedArray :: IsUint8ClampedArray o => o -> Uint8ClampedArray
toUint8ClampedArray = Uint8ClampedArray . coerce
instance IsUint8ClampedArray Uint8ClampedArray
instance IsGObject Uint8ClampedArray where
typeGType _ = gTypeUint8ClampedArray
gTypeUint8ClampedArray :: JSM GType
gTypeUint8ClampedArray = GType . Object <$> jsg "Uint8ClampedArray"
newtype Uint16Array = Uint16Array { unUint16Array :: JSVal }
noUint16Array :: Maybe Uint16Array
noUint16Array = Nothing
{-# INLINE noUint16Array #-}
instance PToJSVal Uint16Array where
pToJSVal = unUint16Array
{-# INLINE pToJSVal #-}
instance PFromJSVal Uint16Array where
pFromJSVal = Uint16Array
{-# INLINE pFromJSVal #-}
instance ToJSVal Uint16Array where
toJSVal = return . unUint16Array
{-# INLINE toJSVal #-}
instance FromJSVal Uint16Array where
fromJSVal v = fmap Uint16Array <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Uint16Array
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsUint16Array o
toUint16Array :: IsUint16Array o => o -> Uint16Array
toUint16Array = Uint16Array . coerce
instance IsUint16Array Uint16Array
instance IsGObject Uint16Array where
typeGType _ = gTypeUint16Array
gTypeUint16Array :: JSM GType
gTypeUint16Array = GType . Object <$> jsg "Uint16Array"
newtype Uint32Array = Uint32Array { unUint32Array :: JSVal }
noUint32Array :: Maybe Uint32Array
noUint32Array = Nothing
{-# INLINE noUint32Array #-}
instance PToJSVal Uint32Array where
pToJSVal = unUint32Array
{-# INLINE pToJSVal #-}
instance PFromJSVal Uint32Array where
pFromJSVal = Uint32Array
{-# INLINE pFromJSVal #-}
instance ToJSVal Uint32Array where
toJSVal = return . unUint32Array
{-# INLINE toJSVal #-}
instance FromJSVal Uint32Array where
fromJSVal v = fmap Uint32Array <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Uint32Array
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsUint32Array o
toUint32Array :: IsUint32Array o => o -> Uint32Array
toUint32Array = Uint32Array . coerce
instance IsUint32Array Uint32Array
instance IsGObject Uint32Array where
typeGType _ = gTypeUint32Array
gTypeUint32Array :: JSM GType
gTypeUint32Array = GType . Object <$> jsg "Uint32Array"
newtype Int8Array = Int8Array { unInt8Array :: JSVal }
noInt8Array :: Maybe Int8Array
noInt8Array = Nothing
{-# INLINE noInt8Array #-}
instance PToJSVal Int8Array where
pToJSVal = unInt8Array
{-# INLINE pToJSVal #-}
instance PFromJSVal Int8Array where
pFromJSVal = Int8Array
{-# INLINE pFromJSVal #-}
instance ToJSVal Int8Array where
toJSVal = return . unInt8Array
{-# INLINE toJSVal #-}
instance FromJSVal Int8Array where
fromJSVal v = fmap Int8Array <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Int8Array
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsInt8Array o
toInt8Array :: IsInt8Array o => o -> Int8Array
toInt8Array = Int8Array . coerce
instance IsInt8Array Int8Array
instance IsGObject Int8Array where
typeGType _ = gTypeInt8Array
gTypeInt8Array :: JSM GType
gTypeInt8Array = GType . Object <$> jsg "Int8Array"
newtype Int16Array = Int16Array { unInt16Array :: JSVal }
noInt16Array :: Maybe Int16Array
noInt16Array = Nothing
{-# INLINE noInt16Array #-}
instance PToJSVal Int16Array where
pToJSVal = unInt16Array
{-# INLINE pToJSVal #-}
instance PFromJSVal Int16Array where
pFromJSVal = Int16Array
{-# INLINE pFromJSVal #-}
instance ToJSVal Int16Array where
toJSVal = return . unInt16Array
{-# INLINE toJSVal #-}
instance FromJSVal Int16Array where
fromJSVal v = fmap Int16Array <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Int16Array
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsInt16Array o
toInt16Array :: IsInt16Array o => o -> Int16Array
toInt16Array = Int16Array . coerce
instance IsInt16Array Int16Array
instance IsGObject Int16Array where
typeGType _ = gTypeInt16Array
gTypeInt16Array :: JSM GType
gTypeInt16Array = GType . Object <$> jsg "Int16Array"
newtype Int32Array = Int32Array { unInt32Array :: JSVal }
noInt32Array :: Maybe Int32Array
noInt32Array = Nothing
{-# INLINE noInt32Array #-}
instance PToJSVal Int32Array where
pToJSVal = unInt32Array
{-# INLINE pToJSVal #-}
instance PFromJSVal Int32Array where
pFromJSVal = Int32Array
{-# INLINE pFromJSVal #-}
instance ToJSVal Int32Array where
toJSVal = return . unInt32Array
{-# INLINE toJSVal #-}
instance FromJSVal Int32Array where
fromJSVal v = fmap Int32Array <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Int32Array
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsInt32Array o
toInt32Array :: IsInt32Array o => o -> Int32Array
toInt32Array = Int32Array . coerce
instance IsInt32Array Int32Array
instance IsGObject Int32Array where
typeGType _ = gTypeInt32Array
gTypeInt32Array :: JSM GType
gTypeInt32Array = GType . Object <$> jsg "Int32Array"
newtype ObjectArray = ObjectArray { unObjectArray :: JSVal }
noObjectArray :: Maybe ObjectArray
noObjectArray = Nothing
{-# INLINE noObjectArray #-}
instance PToJSVal ObjectArray where
pToJSVal = unObjectArray
{-# INLINE pToJSVal #-}
instance PFromJSVal ObjectArray where
pFromJSVal = ObjectArray
{-# INLINE pFromJSVal #-}
instance ToJSVal ObjectArray where
toJSVal = return . unObjectArray
{-# INLINE toJSVal #-}
instance FromJSVal ObjectArray where
fromJSVal v = fmap ObjectArray <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ObjectArray
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsObjectArray o
toObjectArray :: IsObjectArray o => o -> ObjectArray
toObjectArray = ObjectArray . coerce
instance IsObjectArray ObjectArray
instance IsGObject ObjectArray where
typeGType _ = error "Unable to get the JavaScript type of ObjectArray"
newtype ArrayBufferView = ArrayBufferView { unArrayBufferView :: JSVal }
noArrayBufferView :: Maybe ArrayBufferView
noArrayBufferView = Nothing
{-# INLINE noArrayBufferView #-}
instance PToJSVal ArrayBufferView where
pToJSVal = unArrayBufferView
{-# INLINE pToJSVal #-}
instance PFromJSVal ArrayBufferView where
pFromJSVal = ArrayBufferView
{-# INLINE pFromJSVal #-}
instance ToJSVal ArrayBufferView where
toJSVal = return . unArrayBufferView
{-# INLINE toJSVal #-}
instance FromJSVal ArrayBufferView where
fromJSVal v = fmap ArrayBufferView <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ArrayBufferView
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsArrayBufferView o
toArrayBufferView :: IsArrayBufferView o => o -> ArrayBufferView
toArrayBufferView = ArrayBufferView . coerce
instance IsArrayBufferView ArrayBufferView
instance IsGObject ArrayBufferView where
typeGType _ = error "Unable to get the JavaScript type of ArrayBufferView"
newtype Array = Array { unArray :: JSVal }
noArray :: Maybe Array
noArray = Nothing
{-# INLINE noArray #-}
instance PToJSVal Array where
pToJSVal = unArray
{-# INLINE pToJSVal #-}
instance PFromJSVal Array where
pFromJSVal = Array
{-# INLINE pFromJSVal #-}
instance ToJSVal Array where
toJSVal = return . unArray
{-# INLINE toJSVal #-}
instance FromJSVal Array where
fromJSVal v = fmap Array <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Array
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsArray o
toArray :: IsArray o => o -> Array
toArray = Array . coerce
instance IsArray Array
instance IsGObject Array where
typeGType _ = gTypeArray
gTypeArray :: JSM GType
gTypeArray = GType . Object <$> jsg "Array"
newtype Date = Date { unDate :: JSVal }
noDate :: Maybe Date
noDate = Nothing
{-# INLINE noDate #-}
instance PToJSVal Date where
pToJSVal = unDate
{-# INLINE pToJSVal #-}
instance PFromJSVal Date where
pFromJSVal = Date
{-# INLINE pFromJSVal #-}
instance ToJSVal Date where
toJSVal = return . unDate
{-# INLINE toJSVal #-}
instance FromJSVal Date where
fromJSVal v = fmap Date <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Date
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsDate o
toDate :: IsDate o => o -> Date
toDate = Date . coerce
instance IsDate Date
instance IsGObject Date where
typeGType _ = gTypeDate
gTypeDate :: JSM GType
gTypeDate = GType . Object <$> jsg "Date"
newtype Algorithm = Algorithm { unAlgorithm :: JSVal }
noAlgorithm :: Maybe Algorithm
noAlgorithm = Nothing
{-# INLINE noAlgorithm #-}
instance PToJSVal Algorithm where
pToJSVal = unAlgorithm
{-# INLINE pToJSVal #-}
instance PFromJSVal Algorithm where
pFromJSVal = Algorithm
{-# INLINE pFromJSVal #-}
instance ToJSVal Algorithm where
toJSVal = return . unAlgorithm
{-# INLINE toJSVal #-}
instance FromJSVal Algorithm where
fromJSVal v = fmap Algorithm <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Algorithm
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsAlgorithm o
toAlgorithm :: IsAlgorithm o => o -> Algorithm
toAlgorithm = Algorithm . coerce
instance IsAlgorithm Algorithm
instance IsGObject Algorithm where
typeGType _ = error "Unable to get the JavaScript type of Algorithm"
newtype CryptoOperationData = CryptoOperationData { unCryptoOperationData :: JSVal }
noCryptoOperationData :: Maybe CryptoOperationData
noCryptoOperationData = Nothing
{-# INLINE noCryptoOperationData #-}
instance PToJSVal CryptoOperationData where
pToJSVal = unCryptoOperationData
{-# INLINE pToJSVal #-}
instance PFromJSVal CryptoOperationData where
pFromJSVal = CryptoOperationData
{-# INLINE pFromJSVal #-}
instance ToJSVal CryptoOperationData where
toJSVal = return . unCryptoOperationData
{-# INLINE toJSVal #-}
instance FromJSVal CryptoOperationData where
fromJSVal v = fmap CryptoOperationData <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CryptoOperationData
{-# INLINE fromJSValUnchecked #-}
class IsGObject o => IsCryptoOperationData o
toCryptoOperationData :: IsCryptoOperationData o => o -> CryptoOperationData
toCryptoOperationData = CryptoOperationData . coerce
instance IsCryptoOperationData CryptoOperationData
instance IsGObject CryptoOperationData where
typeGType _ = error "Unable to get the JavaScript type of CryptoOperationData"
instance IsCryptoOperationData ArrayBuffer
instance IsCryptoOperationData ArrayBufferView
type GLenum = Word32
noGLenum :: Maybe GLenum
noGLenum = Nothing
{-# INLINE noGLenum #-}
type GLboolean = Bool
noGLboolean :: Maybe GLboolean
noGLboolean = Nothing
{-# INLINE noGLboolean #-}
type GLbitfield = Word32
noGLbitfield :: Maybe GLbitfield
noGLbitfield = Nothing
{-# INLINE noGLbitfield #-}
type GLbyte = Int8
noGLbyte :: Maybe GLbyte
noGLbyte = Nothing
{-# INLINE noGLbyte #-}
type GLshort = Int16
noGLshort :: Maybe GLshort
noGLshort = Nothing
{-# INLINE noGLshort #-}
type GLint = Int32
noGLint :: Maybe GLint
noGLint = Nothing
{-# INLINE noGLint #-}
type GLint64 = Int64
noGLint64 :: Maybe GLint64
noGLint64 = Nothing
{-# INLINE noGLint64 #-}
type GLsizei = Int32
noGLsizei :: Maybe GLsizei
noGLsizei = Nothing
{-# INLINE noGLsizei #-}
type GLintptr = Int64
noGLintptr :: Maybe GLintptr
noGLintptr = Nothing
{-# INLINE noGLintptr #-}
type GLsizeiptr = Int64
noGLsizeiptr :: Maybe GLsizeiptr
noGLsizeiptr = Nothing
{-# INLINE noGLsizeiptr #-}
type GLubyte = Word8
noGLubyte :: Maybe GLubyte
noGLubyte = Nothing
{-# INLINE noGLubyte #-}
type GLushort = Word16
noGLushort :: Maybe GLushort
noGLushort = Nothing
{-# INLINE noGLushort #-}
type GLuint = Word32
noGLuint :: Maybe GLuint
noGLuint = Nothing
{-# INLINE noGLuint #-}
type GLuint64 = Word64
noGLuint64 :: Maybe GLuint64
noGLuint64 = Nothing
{-# INLINE noGLuint64 #-}
type GLfloat = Double
noGLfloat :: Maybe GLfloat
noGLfloat = Nothing
{-# INLINE noGLfloat #-}
type GLclampf = Double
noGLclampf :: Maybe GLclampf
noGLclampf = Nothing
{-# INLINE noGLclampf #-}
newtype AddEventListenerOptionsOrBool = AddEventListenerOptionsOrBool { unAddEventListenerOptionsOrBool :: JSVal }
instance PToJSVal AddEventListenerOptionsOrBool where
pToJSVal = unAddEventListenerOptionsOrBool
{-# INLINE pToJSVal #-}
instance PFromJSVal AddEventListenerOptionsOrBool where
pFromJSVal = AddEventListenerOptionsOrBool
{-# INLINE pFromJSVal #-}
instance ToJSVal AddEventListenerOptionsOrBool where
toJSVal = return . unAddEventListenerOptionsOrBool
{-# INLINE toJSVal #-}
instance FromJSVal AddEventListenerOptionsOrBool where
fromJSVal v = fmap AddEventListenerOptionsOrBool <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AddEventListenerOptionsOrBool
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AddEventListenerOptionsOrBool where
makeObject = makeObject . unAddEventListenerOptionsOrBool
class (FromJSVal o, ToJSVal o, PToJSVal o) => IsAddEventListenerOptionsOrBool o
toAddEventListenerOptionsOrBool :: IsAddEventListenerOptionsOrBool o => o -> AddEventListenerOptionsOrBool
toAddEventListenerOptionsOrBool = AddEventListenerOptionsOrBool . pToJSVal
instance IsAddEventListenerOptionsOrBool AddEventListenerOptionsOrBool
instance IsAddEventListenerOptionsOrBool Bool
instance IsAddEventListenerOptionsOrBool AddEventListenerOptions
newtype BinaryData = BinaryData { unBinaryData :: JSVal }
instance PToJSVal BinaryData where
pToJSVal = unBinaryData
{-# INLINE pToJSVal #-}
instance PFromJSVal BinaryData where
pFromJSVal = BinaryData
{-# INLINE pFromJSVal #-}
instance ToJSVal BinaryData where
toJSVal = return . unBinaryData
{-# INLINE toJSVal #-}
instance FromJSVal BinaryData where
fromJSVal v = fmap BinaryData <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BinaryData
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BinaryData where
makeObject = makeObject . unBinaryData
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBinaryData o
toBinaryData :: IsBinaryData o => o -> BinaryData
toBinaryData = BinaryData . coerce
instance IsBinaryData BinaryData
instance IsBinaryData ArrayBuffer
instance IsBinaryData ArrayBufferView
newtype BlobPart = BlobPart { unBlobPart :: JSVal }
instance PToJSVal BlobPart where
pToJSVal = unBlobPart
{-# INLINE pToJSVal #-}
instance PFromJSVal BlobPart where
pFromJSVal = BlobPart
{-# INLINE pFromJSVal #-}
instance ToJSVal BlobPart where
toJSVal = return . unBlobPart
{-# INLINE toJSVal #-}
instance FromJSVal BlobPart where
fromJSVal v = fmap BlobPart <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BlobPart
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BlobPart where
makeObject = makeObject . unBlobPart
class (FromJSVal o, ToJSVal o) => IsBlobPart o
instance IsBlobPart BlobPart
instance IsBlobPart BinaryData
instance IsBlobPart BufferSource
instance IsBlobPart ArrayBufferView
instance IsBlobPart ArrayBuffer
instance IsBlobPart Blob
instance IsBlobPart File
instance IsBlobPart Text
instance IsBlobPart JSString
instance IsBlobPart String
newtype BodyInit = BodyInit { unBodyInit :: JSVal }
instance PToJSVal BodyInit where
pToJSVal = unBodyInit
{-# INLINE pToJSVal #-}
instance PFromJSVal BodyInit where
pFromJSVal = BodyInit
{-# INLINE pFromJSVal #-}
instance ToJSVal BodyInit where
toJSVal = return . unBodyInit
{-# INLINE toJSVal #-}
instance FromJSVal BodyInit where
fromJSVal v = fmap BodyInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BodyInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BodyInit where
makeObject = makeObject . unBodyInit
class (FromJSVal o, ToJSVal o) => IsBodyInit o
instance IsBodyInit BodyInit
instance IsBodyInit Text
instance IsBodyInit JSString
instance IsBodyInit String
instance IsBodyInit FormData
instance IsBodyInit BinaryData
instance IsBodyInit BufferSource
instance IsBodyInit ArrayBufferView
instance IsBodyInit ArrayBuffer
instance IsBodyInit Blob
instance IsBodyInit File
newtype BufferDataSource = BufferDataSource { unBufferDataSource :: JSVal }
instance PToJSVal BufferDataSource where
pToJSVal = unBufferDataSource
{-# INLINE pToJSVal #-}
instance PFromJSVal BufferDataSource where
pFromJSVal = BufferDataSource
{-# INLINE pFromJSVal #-}
instance ToJSVal BufferDataSource where
toJSVal = return . unBufferDataSource
{-# INLINE toJSVal #-}
instance FromJSVal BufferDataSource where
fromJSVal v = fmap BufferDataSource <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BufferDataSource
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BufferDataSource where
makeObject = makeObject . unBufferDataSource
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBufferDataSource o
toBufferDataSource :: IsBufferDataSource o => o -> BufferDataSource
toBufferDataSource = BufferDataSource . coerce
instance IsBufferDataSource BufferDataSource
instance IsBufferDataSource ArrayBuffer
instance IsBufferDataSource ArrayBufferView
newtype BufferSource = BufferSource { unBufferSource :: JSVal }
instance PToJSVal BufferSource where
pToJSVal = unBufferSource
{-# INLINE pToJSVal #-}
instance PFromJSVal BufferSource where
pFromJSVal = BufferSource
{-# INLINE pFromJSVal #-}
instance ToJSVal BufferSource where
toJSVal = return . unBufferSource
{-# INLINE toJSVal #-}
instance FromJSVal BufferSource where
fromJSVal v = fmap BufferSource <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BufferSource
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BufferSource where
makeObject = makeObject . unBufferSource
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBufferSource o
toBufferSource :: IsBufferSource o => o -> BufferSource
toBufferSource = BufferSource . coerce
instance IsBufferSource BufferSource
instance IsBufferSource ArrayBuffer
instance IsBufferSource ArrayBufferView
newtype CanvasImageSource = CanvasImageSource { unCanvasImageSource :: JSVal }
instance PToJSVal CanvasImageSource where
pToJSVal = unCanvasImageSource
{-# INLINE pToJSVal #-}
instance PFromJSVal CanvasImageSource where
pFromJSVal = CanvasImageSource
{-# INLINE pFromJSVal #-}
instance ToJSVal CanvasImageSource where
toJSVal = return . unCanvasImageSource
{-# INLINE toJSVal #-}
instance FromJSVal CanvasImageSource where
fromJSVal v = fmap CanvasImageSource <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CanvasImageSource
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CanvasImageSource where
makeObject = makeObject . unCanvasImageSource
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCanvasImageSource o
toCanvasImageSource :: IsCanvasImageSource o => o -> CanvasImageSource
toCanvasImageSource = CanvasImageSource . coerce
instance IsCanvasImageSource CanvasImageSource
instance IsCanvasImageSource HTMLImageElement
instance IsCanvasImageSource HTMLVideoElement
instance IsCanvasImageSource HTMLCanvasElement
newtype CanvasStyle = CanvasStyle { unCanvasStyle :: JSVal }
instance PToJSVal CanvasStyle where
pToJSVal = unCanvasStyle
{-# INLINE pToJSVal #-}
instance PFromJSVal CanvasStyle where
pFromJSVal = CanvasStyle
{-# INLINE pFromJSVal #-}
instance ToJSVal CanvasStyle where
toJSVal = return . unCanvasStyle
{-# INLINE toJSVal #-}
instance FromJSVal CanvasStyle where
fromJSVal v = fmap CanvasStyle <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CanvasStyle
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CanvasStyle where
makeObject = makeObject . unCanvasStyle
class (FromJSVal o, ToJSVal o) => IsCanvasStyle o
instance IsCanvasStyle CanvasStyle
instance IsCanvasStyle CanvasPattern
instance IsCanvasStyle CanvasGradient
instance IsCanvasStyle Text
instance IsCanvasStyle JSString
instance IsCanvasStyle String
newtype CredentialBodyType = CredentialBodyType { unCredentialBodyType :: JSVal }
instance PToJSVal CredentialBodyType where
pToJSVal = unCredentialBodyType
{-# INLINE pToJSVal #-}
instance PFromJSVal CredentialBodyType where
pFromJSVal = CredentialBodyType
{-# INLINE pFromJSVal #-}
instance ToJSVal CredentialBodyType where
toJSVal = return . unCredentialBodyType
{-# INLINE toJSVal #-}
instance FromJSVal CredentialBodyType where
fromJSVal v = fmap CredentialBodyType <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CredentialBodyType
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CredentialBodyType where
makeObject = makeObject . unCredentialBodyType
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCredentialBodyType o
toCredentialBodyType :: IsCredentialBodyType o => o -> CredentialBodyType
toCredentialBodyType = CredentialBodyType . coerce
instance IsCredentialBodyType CredentialBodyType
instance IsCredentialBodyType URLSearchParams
instance IsCredentialBodyType FormData
newtype CryptoKeyOrKeyPair = CryptoKeyOrKeyPair { unCryptoKeyOrKeyPair :: JSVal }
instance PToJSVal CryptoKeyOrKeyPair where
pToJSVal = unCryptoKeyOrKeyPair
{-# INLINE pToJSVal #-}
instance PFromJSVal CryptoKeyOrKeyPair where
pFromJSVal = CryptoKeyOrKeyPair
{-# INLINE pFromJSVal #-}
instance ToJSVal CryptoKeyOrKeyPair where
toJSVal = return . unCryptoKeyOrKeyPair
{-# INLINE toJSVal #-}
instance FromJSVal CryptoKeyOrKeyPair where
fromJSVal v = fmap CryptoKeyOrKeyPair <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CryptoKeyOrKeyPair
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CryptoKeyOrKeyPair where
makeObject = makeObject . unCryptoKeyOrKeyPair
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCryptoKeyOrKeyPair o
toCryptoKeyOrKeyPair :: IsCryptoKeyOrKeyPair o => o -> CryptoKeyOrKeyPair
toCryptoKeyOrKeyPair = CryptoKeyOrKeyPair . coerce
instance IsCryptoKeyOrKeyPair CryptoKeyOrKeyPair
instance IsCryptoKeyOrKeyPair CryptoKeyPair
instance IsCryptoKeyOrKeyPair CryptoKey
newtype EventListenerOptionsOrBool = EventListenerOptionsOrBool { unEventListenerOptionsOrBool :: JSVal }
instance PToJSVal EventListenerOptionsOrBool where
pToJSVal = unEventListenerOptionsOrBool
{-# INLINE pToJSVal #-}
instance PFromJSVal EventListenerOptionsOrBool where
pFromJSVal = EventListenerOptionsOrBool
{-# INLINE pFromJSVal #-}
instance ToJSVal EventListenerOptionsOrBool where
toJSVal = return . unEventListenerOptionsOrBool
{-# INLINE toJSVal #-}
instance FromJSVal EventListenerOptionsOrBool where
fromJSVal v = fmap EventListenerOptionsOrBool <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EventListenerOptionsOrBool
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EventListenerOptionsOrBool where
makeObject = makeObject . unEventListenerOptionsOrBool
class (FromJSVal o, ToJSVal o, PToJSVal o) => IsEventListenerOptionsOrBool o
toEventListenerOptionsOrBool :: IsEventListenerOptionsOrBool o => o -> EventListenerOptionsOrBool
toEventListenerOptionsOrBool = EventListenerOptionsOrBool . pToJSVal
instance IsEventListenerOptionsOrBool EventListenerOptionsOrBool
instance IsEventListenerOptionsOrBool Bool
instance IsEventListenerOptionsOrBool EventListenerOptions
instance IsEventListenerOptionsOrBool AddEventListenerOptions
newtype Float32List = Float32List { unFloat32List :: JSVal }
instance PToJSVal Float32List where
pToJSVal = unFloat32List
{-# INLINE pToJSVal #-}
instance PFromJSVal Float32List where
pFromJSVal = Float32List
{-# INLINE pFromJSVal #-}
instance ToJSVal Float32List where
toJSVal = return . unFloat32List
{-# INLINE toJSVal #-}
instance FromJSVal Float32List where
fromJSVal v = fmap Float32List <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Float32List
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Float32List where
makeObject = makeObject . unFloat32List
class (FromJSVal o, ToJSVal o) => IsFloat32List o
instance IsFloat32List Float32List
instance IsFloat32List [GLfloat]
instance IsFloat32List Float32Array
newtype HTMLCollectionOrElement = HTMLCollectionOrElement { unHTMLCollectionOrElement :: JSVal }
instance PToJSVal HTMLCollectionOrElement where
pToJSVal = unHTMLCollectionOrElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLCollectionOrElement where
pFromJSVal = HTMLCollectionOrElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLCollectionOrElement where
toJSVal = return . unHTMLCollectionOrElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLCollectionOrElement where
fromJSVal v = fmap HTMLCollectionOrElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLCollectionOrElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLCollectionOrElement where
makeObject = makeObject . unHTMLCollectionOrElement
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsHTMLCollectionOrElement o
toHTMLCollectionOrElement :: IsHTMLCollectionOrElement o => o -> HTMLCollectionOrElement
toHTMLCollectionOrElement = HTMLCollectionOrElement . coerce
instance IsHTMLCollectionOrElement HTMLCollectionOrElement
instance IsHTMLCollectionOrElement Element
instance IsHTMLCollectionOrElement SVGViewElement
instance IsHTMLCollectionOrElement SVGVKernElement
instance IsHTMLCollectionOrElement SVGUseElement
instance IsHTMLCollectionOrElement SVGTitleElement
instance IsHTMLCollectionOrElement SVGTextPositioningElement
instance IsHTMLCollectionOrElement SVGTextPathElement
instance IsHTMLCollectionOrElement SVGTextElement
instance IsHTMLCollectionOrElement SVGTextContentElement
instance IsHTMLCollectionOrElement SVGTSpanElement
instance IsHTMLCollectionOrElement SVGTRefElement
instance IsHTMLCollectionOrElement SVGSymbolElement
instance IsHTMLCollectionOrElement SVGSwitchElement
instance IsHTMLCollectionOrElement SVGStyleElement
instance IsHTMLCollectionOrElement SVGStopElement
instance IsHTMLCollectionOrElement SVGSetElement
instance IsHTMLCollectionOrElement SVGScriptElement
instance IsHTMLCollectionOrElement SVGSVGElement
instance IsHTMLCollectionOrElement SVGRectElement
instance IsHTMLCollectionOrElement SVGRadialGradientElement
instance IsHTMLCollectionOrElement SVGPolylineElement
instance IsHTMLCollectionOrElement SVGPolygonElement
instance IsHTMLCollectionOrElement SVGPatternElement
instance IsHTMLCollectionOrElement SVGPathElement
instance IsHTMLCollectionOrElement SVGMissingGlyphElement
instance IsHTMLCollectionOrElement SVGMetadataElement
instance IsHTMLCollectionOrElement SVGMaskElement
instance IsHTMLCollectionOrElement SVGMarkerElement
instance IsHTMLCollectionOrElement SVGMPathElement
instance IsHTMLCollectionOrElement SVGLinearGradientElement
instance IsHTMLCollectionOrElement SVGLineElement
instance IsHTMLCollectionOrElement SVGImageElement
instance IsHTMLCollectionOrElement SVGHKernElement
instance IsHTMLCollectionOrElement SVGGraphicsElement
instance IsHTMLCollectionOrElement SVGGradientElement
instance IsHTMLCollectionOrElement SVGGlyphRefElement
instance IsHTMLCollectionOrElement SVGGlyphElement
instance IsHTMLCollectionOrElement SVGGElement
instance IsHTMLCollectionOrElement SVGForeignObjectElement
instance IsHTMLCollectionOrElement SVGFontFaceUriElement
instance IsHTMLCollectionOrElement SVGFontFaceSrcElement
instance IsHTMLCollectionOrElement SVGFontFaceNameElement
instance IsHTMLCollectionOrElement SVGFontFaceFormatElement
instance IsHTMLCollectionOrElement SVGFontFaceElement
instance IsHTMLCollectionOrElement SVGFontElement
instance IsHTMLCollectionOrElement SVGFilterElement
instance IsHTMLCollectionOrElement SVGFETurbulenceElement
instance IsHTMLCollectionOrElement SVGFETileElement
instance IsHTMLCollectionOrElement SVGFESpotLightElement
instance IsHTMLCollectionOrElement SVGFESpecularLightingElement
instance IsHTMLCollectionOrElement SVGFEPointLightElement
instance IsHTMLCollectionOrElement SVGFEOffsetElement
instance IsHTMLCollectionOrElement SVGFEMorphologyElement
instance IsHTMLCollectionOrElement SVGFEMergeNodeElement
instance IsHTMLCollectionOrElement SVGFEMergeElement
instance IsHTMLCollectionOrElement SVGFEImageElement
instance IsHTMLCollectionOrElement SVGFEGaussianBlurElement
instance IsHTMLCollectionOrElement SVGFEFuncRElement
instance IsHTMLCollectionOrElement SVGFEFuncGElement
instance IsHTMLCollectionOrElement SVGFEFuncBElement
instance IsHTMLCollectionOrElement SVGFEFuncAElement
instance IsHTMLCollectionOrElement SVGFEFloodElement
instance IsHTMLCollectionOrElement SVGFEDropShadowElement
instance IsHTMLCollectionOrElement SVGFEDistantLightElement
instance IsHTMLCollectionOrElement SVGFEDisplacementMapElement
instance IsHTMLCollectionOrElement SVGFEDiffuseLightingElement
instance IsHTMLCollectionOrElement SVGFEConvolveMatrixElement
instance IsHTMLCollectionOrElement SVGFECompositeElement
instance IsHTMLCollectionOrElement SVGFEComponentTransferElement
instance IsHTMLCollectionOrElement SVGFEColorMatrixElement
instance IsHTMLCollectionOrElement SVGFEBlendElement
instance IsHTMLCollectionOrElement SVGEllipseElement
instance IsHTMLCollectionOrElement SVGElement
instance IsHTMLCollectionOrElement SVGDescElement
instance IsHTMLCollectionOrElement SVGDefsElement
instance IsHTMLCollectionOrElement SVGCursorElement
instance IsHTMLCollectionOrElement SVGComponentTransferFunctionElement
instance IsHTMLCollectionOrElement SVGClipPathElement
instance IsHTMLCollectionOrElement SVGCircleElement
instance IsHTMLCollectionOrElement SVGAnimationElement
instance IsHTMLCollectionOrElement SVGAnimateTransformElement
instance IsHTMLCollectionOrElement SVGAnimateMotionElement
instance IsHTMLCollectionOrElement SVGAnimateElement
instance IsHTMLCollectionOrElement SVGAnimateColorElement
instance IsHTMLCollectionOrElement SVGAltGlyphItemElement
instance IsHTMLCollectionOrElement SVGAltGlyphElement
instance IsHTMLCollectionOrElement SVGAltGlyphDefElement
instance IsHTMLCollectionOrElement SVGAElement
instance IsHTMLCollectionOrElement HTMLVideoElement
instance IsHTMLCollectionOrElement HTMLUnknownElement
instance IsHTMLCollectionOrElement HTMLUListElement
instance IsHTMLCollectionOrElement HTMLTrackElement
instance IsHTMLCollectionOrElement HTMLTitleElement
instance IsHTMLCollectionOrElement HTMLTimeElement
instance IsHTMLCollectionOrElement HTMLTextAreaElement
instance IsHTMLCollectionOrElement HTMLTemplateElement
instance IsHTMLCollectionOrElement HTMLTableSectionElement
instance IsHTMLCollectionOrElement HTMLTableRowElement
instance IsHTMLCollectionOrElement HTMLTableElement
instance IsHTMLCollectionOrElement HTMLTableColElement
instance IsHTMLCollectionOrElement HTMLTableCellElement
instance IsHTMLCollectionOrElement HTMLTableCaptionElement
instance IsHTMLCollectionOrElement HTMLStyleElement
instance IsHTMLCollectionOrElement HTMLSpanElement
instance IsHTMLCollectionOrElement HTMLSourceElement
instance IsHTMLCollectionOrElement HTMLSlotElement
instance IsHTMLCollectionOrElement HTMLSelectElement
instance IsHTMLCollectionOrElement HTMLScriptElement
instance IsHTMLCollectionOrElement HTMLQuoteElement
instance IsHTMLCollectionOrElement HTMLProgressElement
instance IsHTMLCollectionOrElement HTMLPreElement
instance IsHTMLCollectionOrElement HTMLPictureElement
instance IsHTMLCollectionOrElement HTMLParamElement
instance IsHTMLCollectionOrElement HTMLParagraphElement
instance IsHTMLCollectionOrElement HTMLOutputElement
instance IsHTMLCollectionOrElement HTMLOptionElement
instance IsHTMLCollectionOrElement HTMLOptGroupElement
instance IsHTMLCollectionOrElement HTMLObjectElement
instance IsHTMLCollectionOrElement HTMLOListElement
instance IsHTMLCollectionOrElement HTMLModElement
instance IsHTMLCollectionOrElement HTMLMeterElement
instance IsHTMLCollectionOrElement HTMLMetaElement
instance IsHTMLCollectionOrElement HTMLMenuElement
instance IsHTMLCollectionOrElement HTMLMediaElement
instance IsHTMLCollectionOrElement HTMLMarqueeElement
instance IsHTMLCollectionOrElement HTMLMapElement
instance IsHTMLCollectionOrElement HTMLLinkElement
instance IsHTMLCollectionOrElement HTMLLegendElement
instance IsHTMLCollectionOrElement HTMLLabelElement
instance IsHTMLCollectionOrElement HTMLLIElement
instance IsHTMLCollectionOrElement HTMLKeygenElement
instance IsHTMLCollectionOrElement HTMLInputElement
instance IsHTMLCollectionOrElement HTMLImageElement
instance IsHTMLCollectionOrElement HTMLIFrameElement
instance IsHTMLCollectionOrElement HTMLHtmlElement
instance IsHTMLCollectionOrElement HTMLHeadingElement
instance IsHTMLCollectionOrElement HTMLHeadElement
instance IsHTMLCollectionOrElement HTMLHRElement
instance IsHTMLCollectionOrElement HTMLFrameSetElement
instance IsHTMLCollectionOrElement HTMLFrameElement
instance IsHTMLCollectionOrElement HTMLFormElement
instance IsHTMLCollectionOrElement HTMLFontElement
instance IsHTMLCollectionOrElement HTMLFieldSetElement
instance IsHTMLCollectionOrElement HTMLEmbedElement
instance IsHTMLCollectionOrElement HTMLElement
instance IsHTMLCollectionOrElement HTMLDivElement
instance IsHTMLCollectionOrElement HTMLDirectoryElement
instance IsHTMLCollectionOrElement HTMLDetailsElement
instance IsHTMLCollectionOrElement HTMLDataListElement
instance IsHTMLCollectionOrElement HTMLDataElement
instance IsHTMLCollectionOrElement HTMLDListElement
instance IsHTMLCollectionOrElement HTMLCanvasElement
instance IsHTMLCollectionOrElement HTMLButtonElement
instance IsHTMLCollectionOrElement HTMLBodyElement
instance IsHTMLCollectionOrElement HTMLBaseElement
instance IsHTMLCollectionOrElement HTMLBRElement
instance IsHTMLCollectionOrElement HTMLAudioElement
instance IsHTMLCollectionOrElement HTMLAttachmentElement
instance IsHTMLCollectionOrElement HTMLAreaElement
instance IsHTMLCollectionOrElement HTMLAppletElement
instance IsHTMLCollectionOrElement HTMLAnchorElement
instance IsHTMLCollectionOrElement HTMLCollection
instance IsHTMLCollectionOrElement HTMLOptionsCollection
instance IsHTMLCollectionOrElement HTMLFormControlsCollection
newtype HTMLElementOrLong = HTMLElementOrLong { unHTMLElementOrLong :: JSVal }
instance PToJSVal HTMLElementOrLong where
pToJSVal = unHTMLElementOrLong
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLElementOrLong where
pFromJSVal = HTMLElementOrLong
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLElementOrLong where
toJSVal = return . unHTMLElementOrLong
{-# INLINE toJSVal #-}
instance FromJSVal HTMLElementOrLong where
fromJSVal v = fmap HTMLElementOrLong <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLElementOrLong
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLElementOrLong where
makeObject = makeObject . unHTMLElementOrLong
class (FromJSVal o, ToJSVal o) => IsHTMLElementOrLong o
instance IsHTMLElementOrLong HTMLElementOrLong
instance IsHTMLElementOrLong Int
instance IsHTMLElementOrLong HTMLElement
instance IsHTMLElementOrLong HTMLVideoElement
instance IsHTMLElementOrLong HTMLUnknownElement
instance IsHTMLElementOrLong HTMLUListElement
instance IsHTMLElementOrLong HTMLTrackElement
instance IsHTMLElementOrLong HTMLTitleElement
instance IsHTMLElementOrLong HTMLTimeElement
instance IsHTMLElementOrLong HTMLTextAreaElement
instance IsHTMLElementOrLong HTMLTemplateElement
instance IsHTMLElementOrLong HTMLTableSectionElement
instance IsHTMLElementOrLong HTMLTableRowElement
instance IsHTMLElementOrLong HTMLTableElement
instance IsHTMLElementOrLong HTMLTableColElement
instance IsHTMLElementOrLong HTMLTableCellElement
instance IsHTMLElementOrLong HTMLTableCaptionElement
instance IsHTMLElementOrLong HTMLStyleElement
instance IsHTMLElementOrLong HTMLSpanElement
instance IsHTMLElementOrLong HTMLSourceElement
instance IsHTMLElementOrLong HTMLSlotElement
instance IsHTMLElementOrLong HTMLSelectElement
instance IsHTMLElementOrLong HTMLScriptElement
instance IsHTMLElementOrLong HTMLQuoteElement
instance IsHTMLElementOrLong HTMLProgressElement
instance IsHTMLElementOrLong HTMLPreElement
instance IsHTMLElementOrLong HTMLPictureElement
instance IsHTMLElementOrLong HTMLParamElement
instance IsHTMLElementOrLong HTMLParagraphElement
instance IsHTMLElementOrLong HTMLOutputElement
instance IsHTMLElementOrLong HTMLOptionElement
instance IsHTMLElementOrLong HTMLOptGroupElement
instance IsHTMLElementOrLong HTMLObjectElement
instance IsHTMLElementOrLong HTMLOListElement
instance IsHTMLElementOrLong HTMLModElement
instance IsHTMLElementOrLong HTMLMeterElement
instance IsHTMLElementOrLong HTMLMetaElement
instance IsHTMLElementOrLong HTMLMenuElement
instance IsHTMLElementOrLong HTMLMediaElement
instance IsHTMLElementOrLong HTMLMarqueeElement
instance IsHTMLElementOrLong HTMLMapElement
instance IsHTMLElementOrLong HTMLLinkElement
instance IsHTMLElementOrLong HTMLLegendElement
instance IsHTMLElementOrLong HTMLLabelElement
instance IsHTMLElementOrLong HTMLLIElement
instance IsHTMLElementOrLong HTMLKeygenElement
instance IsHTMLElementOrLong HTMLInputElement
instance IsHTMLElementOrLong HTMLImageElement
instance IsHTMLElementOrLong HTMLIFrameElement
instance IsHTMLElementOrLong HTMLHtmlElement
instance IsHTMLElementOrLong HTMLHeadingElement
instance IsHTMLElementOrLong HTMLHeadElement
instance IsHTMLElementOrLong HTMLHRElement
instance IsHTMLElementOrLong HTMLFrameSetElement
instance IsHTMLElementOrLong HTMLFrameElement
instance IsHTMLElementOrLong HTMLFormElement
instance IsHTMLElementOrLong HTMLFontElement
instance IsHTMLElementOrLong HTMLFieldSetElement
instance IsHTMLElementOrLong HTMLEmbedElement
instance IsHTMLElementOrLong HTMLDivElement
instance IsHTMLElementOrLong HTMLDirectoryElement
instance IsHTMLElementOrLong HTMLDetailsElement
instance IsHTMLElementOrLong HTMLDataListElement
instance IsHTMLElementOrLong HTMLDataElement
instance IsHTMLElementOrLong HTMLDListElement
instance IsHTMLElementOrLong HTMLCanvasElement
instance IsHTMLElementOrLong HTMLButtonElement
instance IsHTMLElementOrLong HTMLBodyElement
instance IsHTMLElementOrLong HTMLBaseElement
instance IsHTMLElementOrLong HTMLBRElement
instance IsHTMLElementOrLong HTMLAudioElement
instance IsHTMLElementOrLong HTMLAttachmentElement
instance IsHTMLElementOrLong HTMLAreaElement
instance IsHTMLElementOrLong HTMLAppletElement
instance IsHTMLElementOrLong HTMLAnchorElement
newtype HTMLOptionElementOrGroup = HTMLOptionElementOrGroup { unHTMLOptionElementOrGroup :: JSVal }
instance PToJSVal HTMLOptionElementOrGroup where
pToJSVal = unHTMLOptionElementOrGroup
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLOptionElementOrGroup where
pFromJSVal = HTMLOptionElementOrGroup
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLOptionElementOrGroup where
toJSVal = return . unHTMLOptionElementOrGroup
{-# INLINE toJSVal #-}
instance FromJSVal HTMLOptionElementOrGroup where
fromJSVal v = fmap HTMLOptionElementOrGroup <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLOptionElementOrGroup
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLOptionElementOrGroup where
makeObject = makeObject . unHTMLOptionElementOrGroup
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsHTMLOptionElementOrGroup o
toHTMLOptionElementOrGroup :: IsHTMLOptionElementOrGroup o => o -> HTMLOptionElementOrGroup
toHTMLOptionElementOrGroup = HTMLOptionElementOrGroup . coerce
instance IsHTMLOptionElementOrGroup HTMLOptionElementOrGroup
instance IsHTMLOptionElementOrGroup HTMLOptGroupElement
instance IsHTMLOptionElementOrGroup HTMLOptionElement
newtype IDBCursorSource = IDBCursorSource { unIDBCursorSource :: JSVal }
instance PToJSVal IDBCursorSource where
pToJSVal = unIDBCursorSource
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBCursorSource where
pFromJSVal = IDBCursorSource
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBCursorSource where
toJSVal = return . unIDBCursorSource
{-# INLINE toJSVal #-}
instance FromJSVal IDBCursorSource where
fromJSVal v = fmap IDBCursorSource <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBCursorSource
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBCursorSource where
makeObject = makeObject . unIDBCursorSource
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBCursorSource o
toIDBCursorSource :: IsIDBCursorSource o => o -> IDBCursorSource
toIDBCursorSource = IDBCursorSource . coerce
instance IsIDBCursorSource IDBCursorSource
instance IsIDBCursorSource IDBIndex
instance IsIDBCursorSource IDBObjectStore
newtype IDBKeyPath = IDBKeyPath { unIDBKeyPath :: JSVal }
instance PToJSVal IDBKeyPath where
pToJSVal = unIDBKeyPath
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBKeyPath where
pFromJSVal = IDBKeyPath
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBKeyPath where
toJSVal = return . unIDBKeyPath
{-# INLINE toJSVal #-}
instance FromJSVal IDBKeyPath where
fromJSVal v = fmap IDBKeyPath <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBKeyPath
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBKeyPath where
makeObject = makeObject . unIDBKeyPath
class (FromJSVal o, ToJSVal o) => IsIDBKeyPath o
instance IsIDBKeyPath IDBKeyPath
instance IsIDBKeyPath [Text]
instance IsIDBKeyPath [JSString]
instance IsIDBKeyPath [String]
instance IsIDBKeyPath Text
instance IsIDBKeyPath JSString
instance IsIDBKeyPath String
newtype IDBRequestResult = IDBRequestResult { unIDBRequestResult :: JSVal }
instance PToJSVal IDBRequestResult where
pToJSVal = unIDBRequestResult
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBRequestResult where
pFromJSVal = IDBRequestResult
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBRequestResult where
toJSVal = return . unIDBRequestResult
{-# INLINE toJSVal #-}
instance FromJSVal IDBRequestResult where
fromJSVal v = fmap IDBRequestResult <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBRequestResult
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBRequestResult where
makeObject = makeObject . unIDBRequestResult
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBRequestResult o
toIDBRequestResult :: IsIDBRequestResult o => o -> IDBRequestResult
toIDBRequestResult = IDBRequestResult . coerce
instance IsIDBRequestResult IDBRequestResult
instance IsIDBRequestResult JSVal
instance IsIDBRequestResult IDBDatabase
instance IsIDBRequestResult IDBCursor
instance IsIDBRequestResult IDBCursorWithValue
newtype IDBRequestSource = IDBRequestSource { unIDBRequestSource :: JSVal }
instance PToJSVal IDBRequestSource where
pToJSVal = unIDBRequestSource
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBRequestSource where
pFromJSVal = IDBRequestSource
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBRequestSource where
toJSVal = return . unIDBRequestSource
{-# INLINE toJSVal #-}
instance FromJSVal IDBRequestSource where
fromJSVal v = fmap IDBRequestSource <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBRequestSource
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBRequestSource where
makeObject = makeObject . unIDBRequestSource
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBRequestSource o
toIDBRequestSource :: IsIDBRequestSource o => o -> IDBRequestSource
toIDBRequestSource = IDBRequestSource . coerce
instance IsIDBRequestSource IDBRequestSource
instance IsIDBRequestSource IDBCursor
instance IsIDBRequestSource IDBCursorWithValue
instance IsIDBRequestSource IDBIndex
instance IsIDBRequestSource IDBObjectStore
newtype Int32List = Int32List { unInt32List :: JSVal }
instance PToJSVal Int32List where
pToJSVal = unInt32List
{-# INLINE pToJSVal #-}
instance PFromJSVal Int32List where
pFromJSVal = Int32List
{-# INLINE pFromJSVal #-}
instance ToJSVal Int32List where
toJSVal = return . unInt32List
{-# INLINE toJSVal #-}
instance FromJSVal Int32List where
fromJSVal v = fmap Int32List <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Int32List
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Int32List where
makeObject = makeObject . unInt32List
class (FromJSVal o, ToJSVal o) => IsInt32List o
instance IsInt32List Int32List
instance IsInt32List [GLint]
instance IsInt32List Int32Array
newtype KeyData = KeyData { unKeyData :: JSVal }
instance PToJSVal KeyData where
pToJSVal = unKeyData
{-# INLINE pToJSVal #-}
instance PFromJSVal KeyData where
pFromJSVal = KeyData
{-# INLINE pFromJSVal #-}
instance ToJSVal KeyData where
toJSVal = return . unKeyData
{-# INLINE toJSVal #-}
instance FromJSVal KeyData where
fromJSVal v = fmap KeyData <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . KeyData
{-# INLINE fromJSValUnchecked #-}
instance MakeObject KeyData where
makeObject = makeObject . unKeyData
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsKeyData o
toKeyData :: IsKeyData o => o -> KeyData
toKeyData = KeyData . coerce
instance IsKeyData KeyData
instance IsKeyData JsonWebKey
instance IsKeyData BinaryData
instance IsKeyData BufferSource
instance IsKeyData ArrayBufferView
instance IsKeyData ArrayBuffer
newtype MediaProvider = MediaProvider { unMediaProvider :: JSVal }
instance PToJSVal MediaProvider where
pToJSVal = unMediaProvider
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaProvider where
pFromJSVal = MediaProvider
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaProvider where
toJSVal = return . unMediaProvider
{-# INLINE toJSVal #-}
instance FromJSVal MediaProvider where
fromJSVal v = fmap MediaProvider <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaProvider
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaProvider where
makeObject = makeObject . unMediaProvider
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsMediaProvider o
toMediaProvider :: IsMediaProvider o => o -> MediaProvider
toMediaProvider = MediaProvider . coerce
instance IsMediaProvider MediaProvider
instance IsMediaProvider MediaStream
instance IsMediaProvider MediaSource
instance IsMediaProvider Blob
instance IsMediaProvider File
newtype MediaStreamTrackOrKind = MediaStreamTrackOrKind { unMediaStreamTrackOrKind :: JSVal }
instance PToJSVal MediaStreamTrackOrKind where
pToJSVal = unMediaStreamTrackOrKind
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaStreamTrackOrKind where
pFromJSVal = MediaStreamTrackOrKind
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaStreamTrackOrKind where
toJSVal = return . unMediaStreamTrackOrKind
{-# INLINE toJSVal #-}
instance FromJSVal MediaStreamTrackOrKind where
fromJSVal v = fmap MediaStreamTrackOrKind <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaStreamTrackOrKind
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaStreamTrackOrKind where
makeObject = makeObject . unMediaStreamTrackOrKind
class (FromJSVal o, ToJSVal o) => IsMediaStreamTrackOrKind o
instance IsMediaStreamTrackOrKind MediaStreamTrackOrKind
instance IsMediaStreamTrackOrKind Text
instance IsMediaStreamTrackOrKind JSString
instance IsMediaStreamTrackOrKind String
instance IsMediaStreamTrackOrKind MediaStreamTrack
instance IsMediaStreamTrackOrKind CanvasCaptureMediaStreamTrack
newtype MessageEventSource = MessageEventSource { unMessageEventSource :: JSVal }
instance PToJSVal MessageEventSource where
pToJSVal = unMessageEventSource
{-# INLINE pToJSVal #-}
instance PFromJSVal MessageEventSource where
pFromJSVal = MessageEventSource
{-# INLINE pFromJSVal #-}
instance ToJSVal MessageEventSource where
toJSVal = return . unMessageEventSource
{-# INLINE toJSVal #-}
instance FromJSVal MessageEventSource where
fromJSVal v = fmap MessageEventSource <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MessageEventSource
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MessageEventSource where
makeObject = makeObject . unMessageEventSource
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsMessageEventSource o
toMessageEventSource :: IsMessageEventSource o => o -> MessageEventSource
toMessageEventSource = MessageEventSource . coerce
instance IsMessageEventSource MessageEventSource
instance IsMessageEventSource MessagePort
instance IsMessageEventSource Window
newtype NodeOrString = NodeOrString { unNodeOrString :: JSVal }
instance PToJSVal NodeOrString where
pToJSVal = unNodeOrString
{-# INLINE pToJSVal #-}
instance PFromJSVal NodeOrString where
pFromJSVal = NodeOrString
{-# INLINE pFromJSVal #-}
instance ToJSVal NodeOrString where
toJSVal = return . unNodeOrString
{-# INLINE toJSVal #-}
instance FromJSVal NodeOrString where
fromJSVal v = fmap NodeOrString <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NodeOrString
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NodeOrString where
makeObject = makeObject . unNodeOrString
class (FromJSVal o, ToJSVal o) => IsNodeOrString o
instance IsNodeOrString NodeOrString
instance IsNodeOrString Text
instance IsNodeOrString JSString
instance IsNodeOrString String
instance IsNodeOrString Node
instance IsNodeOrString XMLDocument
instance IsNodeOrString ShadowRoot
instance IsNodeOrString SVGViewElement
instance IsNodeOrString SVGVKernElement
instance IsNodeOrString SVGUseElement
instance IsNodeOrString SVGTitleElement
instance IsNodeOrString SVGTextPositioningElement
instance IsNodeOrString SVGTextPathElement
instance IsNodeOrString SVGTextElement
instance IsNodeOrString SVGTextContentElement
instance IsNodeOrString SVGTSpanElement
instance IsNodeOrString SVGTRefElement
instance IsNodeOrString SVGSymbolElement
instance IsNodeOrString SVGSwitchElement
instance IsNodeOrString SVGStyleElement
instance IsNodeOrString SVGStopElement
instance IsNodeOrString SVGSetElement
instance IsNodeOrString SVGScriptElement
instance IsNodeOrString SVGSVGElement
instance IsNodeOrString SVGRectElement
instance IsNodeOrString SVGRadialGradientElement
instance IsNodeOrString SVGPolylineElement
instance IsNodeOrString SVGPolygonElement
instance IsNodeOrString SVGPatternElement
instance IsNodeOrString SVGPathElement
instance IsNodeOrString SVGMissingGlyphElement
instance IsNodeOrString SVGMetadataElement
instance IsNodeOrString SVGMaskElement
instance IsNodeOrString SVGMarkerElement
instance IsNodeOrString SVGMPathElement
instance IsNodeOrString SVGLinearGradientElement
instance IsNodeOrString SVGLineElement
instance IsNodeOrString SVGImageElement
instance IsNodeOrString SVGHKernElement
instance IsNodeOrString SVGGraphicsElement
instance IsNodeOrString SVGGradientElement
instance IsNodeOrString SVGGlyphRefElement
instance IsNodeOrString SVGGlyphElement
instance IsNodeOrString SVGGElement
instance IsNodeOrString SVGForeignObjectElement
instance IsNodeOrString SVGFontFaceUriElement
instance IsNodeOrString SVGFontFaceSrcElement
instance IsNodeOrString SVGFontFaceNameElement
instance IsNodeOrString SVGFontFaceFormatElement
instance IsNodeOrString SVGFontFaceElement
instance IsNodeOrString SVGFontElement
instance IsNodeOrString SVGFilterElement
instance IsNodeOrString SVGFETurbulenceElement
instance IsNodeOrString SVGFETileElement
instance IsNodeOrString SVGFESpotLightElement
instance IsNodeOrString SVGFESpecularLightingElement
instance IsNodeOrString SVGFEPointLightElement
instance IsNodeOrString SVGFEOffsetElement
instance IsNodeOrString SVGFEMorphologyElement
instance IsNodeOrString SVGFEMergeNodeElement
instance IsNodeOrString SVGFEMergeElement
instance IsNodeOrString SVGFEImageElement
instance IsNodeOrString SVGFEGaussianBlurElement
instance IsNodeOrString SVGFEFuncRElement
instance IsNodeOrString SVGFEFuncGElement
instance IsNodeOrString SVGFEFuncBElement
instance IsNodeOrString SVGFEFuncAElement
instance IsNodeOrString SVGFEFloodElement
instance IsNodeOrString SVGFEDropShadowElement
instance IsNodeOrString SVGFEDistantLightElement
instance IsNodeOrString SVGFEDisplacementMapElement
instance IsNodeOrString SVGFEDiffuseLightingElement
instance IsNodeOrString SVGFEConvolveMatrixElement
instance IsNodeOrString SVGFECompositeElement
instance IsNodeOrString SVGFEComponentTransferElement
instance IsNodeOrString SVGFEColorMatrixElement
instance IsNodeOrString SVGFEBlendElement
instance IsNodeOrString SVGEllipseElement
instance IsNodeOrString SVGElement
instance IsNodeOrString SVGDescElement
instance IsNodeOrString SVGDefsElement
instance IsNodeOrString SVGCursorElement
instance IsNodeOrString SVGComponentTransferFunctionElement
instance IsNodeOrString SVGClipPathElement
instance IsNodeOrString SVGCircleElement
instance IsNodeOrString SVGAnimationElement
instance IsNodeOrString SVGAnimateTransformElement
instance IsNodeOrString SVGAnimateMotionElement
instance IsNodeOrString SVGAnimateElement
instance IsNodeOrString SVGAnimateColorElement
instance IsNodeOrString SVGAltGlyphItemElement
instance IsNodeOrString SVGAltGlyphElement
instance IsNodeOrString SVGAltGlyphDefElement
instance IsNodeOrString SVGAElement
instance IsNodeOrString ProcessingInstruction
instance IsNodeOrString HTMLVideoElement
instance IsNodeOrString HTMLUnknownElement
instance IsNodeOrString HTMLUListElement
instance IsNodeOrString HTMLTrackElement
instance IsNodeOrString HTMLTitleElement
instance IsNodeOrString HTMLTimeElement
instance IsNodeOrString HTMLTextAreaElement
instance IsNodeOrString HTMLTemplateElement
instance IsNodeOrString HTMLTableSectionElement
instance IsNodeOrString HTMLTableRowElement
instance IsNodeOrString HTMLTableElement
instance IsNodeOrString HTMLTableColElement
instance IsNodeOrString HTMLTableCellElement
instance IsNodeOrString HTMLTableCaptionElement
instance IsNodeOrString HTMLStyleElement
instance IsNodeOrString HTMLSpanElement
instance IsNodeOrString HTMLSourceElement
instance IsNodeOrString HTMLSlotElement
instance IsNodeOrString HTMLSelectElement
instance IsNodeOrString HTMLScriptElement
instance IsNodeOrString HTMLQuoteElement
instance IsNodeOrString HTMLProgressElement
instance IsNodeOrString HTMLPreElement
instance IsNodeOrString HTMLPictureElement
instance IsNodeOrString HTMLParamElement
instance IsNodeOrString HTMLParagraphElement
instance IsNodeOrString HTMLOutputElement
instance IsNodeOrString HTMLOptionElement
instance IsNodeOrString HTMLOptGroupElement
instance IsNodeOrString HTMLObjectElement
instance IsNodeOrString HTMLOListElement
instance IsNodeOrString HTMLModElement
instance IsNodeOrString HTMLMeterElement
instance IsNodeOrString HTMLMetaElement
instance IsNodeOrString HTMLMenuElement
instance IsNodeOrString HTMLMediaElement
instance IsNodeOrString HTMLMarqueeElement
instance IsNodeOrString HTMLMapElement
instance IsNodeOrString HTMLLinkElement
instance IsNodeOrString HTMLLegendElement
instance IsNodeOrString HTMLLabelElement
instance IsNodeOrString HTMLLIElement
instance IsNodeOrString HTMLKeygenElement
instance IsNodeOrString HTMLInputElement
instance IsNodeOrString HTMLImageElement
instance IsNodeOrString HTMLIFrameElement
instance IsNodeOrString HTMLHtmlElement
instance IsNodeOrString HTMLHeadingElement
instance IsNodeOrString HTMLHeadElement
instance IsNodeOrString HTMLHRElement
instance IsNodeOrString HTMLFrameSetElement
instance IsNodeOrString HTMLFrameElement
instance IsNodeOrString HTMLFormElement
instance IsNodeOrString HTMLFontElement
instance IsNodeOrString HTMLFieldSetElement
instance IsNodeOrString HTMLEmbedElement
instance IsNodeOrString HTMLElement
instance IsNodeOrString HTMLDocument
instance IsNodeOrString HTMLDivElement
instance IsNodeOrString HTMLDirectoryElement
instance IsNodeOrString HTMLDetailsElement
instance IsNodeOrString HTMLDataListElement
instance IsNodeOrString HTMLDataElement
instance IsNodeOrString HTMLDListElement
instance IsNodeOrString HTMLCanvasElement
instance IsNodeOrString HTMLButtonElement
instance IsNodeOrString HTMLBodyElement
instance IsNodeOrString HTMLBaseElement
instance IsNodeOrString HTMLBRElement
instance IsNodeOrString HTMLAudioElement
instance IsNodeOrString HTMLAttachmentElement
instance IsNodeOrString HTMLAreaElement
instance IsNodeOrString HTMLAppletElement
instance IsNodeOrString HTMLAnchorElement
instance IsNodeOrString Element
instance IsNodeOrString DocumentType
instance IsNodeOrString DocumentFragment
instance IsNodeOrString Document
instance IsNodeOrString Comment
instance IsNodeOrString CharacterData
instance IsNodeOrString CDATASection
instance IsNodeOrString Attr
newtype RTCIceCandidateOrInit = RTCIceCandidateOrInit { unRTCIceCandidateOrInit :: JSVal }
instance PToJSVal RTCIceCandidateOrInit where
pToJSVal = unRTCIceCandidateOrInit
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCIceCandidateOrInit where
pFromJSVal = RTCIceCandidateOrInit
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCIceCandidateOrInit where
toJSVal = return . unRTCIceCandidateOrInit
{-# INLINE toJSVal #-}
instance FromJSVal RTCIceCandidateOrInit where
fromJSVal v = fmap RTCIceCandidateOrInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCIceCandidateOrInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCIceCandidateOrInit where
makeObject = makeObject . unRTCIceCandidateOrInit
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRTCIceCandidateOrInit o
toRTCIceCandidateOrInit :: IsRTCIceCandidateOrInit o => o -> RTCIceCandidateOrInit
toRTCIceCandidateOrInit = RTCIceCandidateOrInit . coerce
instance IsRTCIceCandidateOrInit RTCIceCandidateOrInit
instance IsRTCIceCandidateOrInit RTCIceCandidate
instance IsRTCIceCandidateOrInit RTCIceCandidateInit
newtype RadioNodeListOrElement = RadioNodeListOrElement { unRadioNodeListOrElement :: JSVal }
instance PToJSVal RadioNodeListOrElement where
pToJSVal = unRadioNodeListOrElement
{-# INLINE pToJSVal #-}
instance PFromJSVal RadioNodeListOrElement where
pFromJSVal = RadioNodeListOrElement
{-# INLINE pFromJSVal #-}
instance ToJSVal RadioNodeListOrElement where
toJSVal = return . unRadioNodeListOrElement
{-# INLINE toJSVal #-}
instance FromJSVal RadioNodeListOrElement where
fromJSVal v = fmap RadioNodeListOrElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RadioNodeListOrElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RadioNodeListOrElement where
makeObject = makeObject . unRadioNodeListOrElement
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRadioNodeListOrElement o
toRadioNodeListOrElement :: IsRadioNodeListOrElement o => o -> RadioNodeListOrElement
toRadioNodeListOrElement = RadioNodeListOrElement . coerce
instance IsRadioNodeListOrElement RadioNodeListOrElement
instance IsRadioNodeListOrElement Element
instance IsRadioNodeListOrElement SVGViewElement
instance IsRadioNodeListOrElement SVGVKernElement
instance IsRadioNodeListOrElement SVGUseElement
instance IsRadioNodeListOrElement SVGTitleElement
instance IsRadioNodeListOrElement SVGTextPositioningElement
instance IsRadioNodeListOrElement SVGTextPathElement
instance IsRadioNodeListOrElement SVGTextElement
instance IsRadioNodeListOrElement SVGTextContentElement
instance IsRadioNodeListOrElement SVGTSpanElement
instance IsRadioNodeListOrElement SVGTRefElement
instance IsRadioNodeListOrElement SVGSymbolElement
instance IsRadioNodeListOrElement SVGSwitchElement
instance IsRadioNodeListOrElement SVGStyleElement
instance IsRadioNodeListOrElement SVGStopElement
instance IsRadioNodeListOrElement SVGSetElement
instance IsRadioNodeListOrElement SVGScriptElement
instance IsRadioNodeListOrElement SVGSVGElement
instance IsRadioNodeListOrElement SVGRectElement
instance IsRadioNodeListOrElement SVGRadialGradientElement
instance IsRadioNodeListOrElement SVGPolylineElement
instance IsRadioNodeListOrElement SVGPolygonElement
instance IsRadioNodeListOrElement SVGPatternElement
instance IsRadioNodeListOrElement SVGPathElement
instance IsRadioNodeListOrElement SVGMissingGlyphElement
instance IsRadioNodeListOrElement SVGMetadataElement
instance IsRadioNodeListOrElement SVGMaskElement
instance IsRadioNodeListOrElement SVGMarkerElement
instance IsRadioNodeListOrElement SVGMPathElement
instance IsRadioNodeListOrElement SVGLinearGradientElement
instance IsRadioNodeListOrElement SVGLineElement
instance IsRadioNodeListOrElement SVGImageElement
instance IsRadioNodeListOrElement SVGHKernElement
instance IsRadioNodeListOrElement SVGGraphicsElement
instance IsRadioNodeListOrElement SVGGradientElement
instance IsRadioNodeListOrElement SVGGlyphRefElement
instance IsRadioNodeListOrElement SVGGlyphElement
instance IsRadioNodeListOrElement SVGGElement
instance IsRadioNodeListOrElement SVGForeignObjectElement
instance IsRadioNodeListOrElement SVGFontFaceUriElement
instance IsRadioNodeListOrElement SVGFontFaceSrcElement
instance IsRadioNodeListOrElement SVGFontFaceNameElement
instance IsRadioNodeListOrElement SVGFontFaceFormatElement
instance IsRadioNodeListOrElement SVGFontFaceElement
instance IsRadioNodeListOrElement SVGFontElement
instance IsRadioNodeListOrElement SVGFilterElement
instance IsRadioNodeListOrElement SVGFETurbulenceElement
instance IsRadioNodeListOrElement SVGFETileElement
instance IsRadioNodeListOrElement SVGFESpotLightElement
instance IsRadioNodeListOrElement SVGFESpecularLightingElement
instance IsRadioNodeListOrElement SVGFEPointLightElement
instance IsRadioNodeListOrElement SVGFEOffsetElement
instance IsRadioNodeListOrElement SVGFEMorphologyElement
instance IsRadioNodeListOrElement SVGFEMergeNodeElement
instance IsRadioNodeListOrElement SVGFEMergeElement
instance IsRadioNodeListOrElement SVGFEImageElement
instance IsRadioNodeListOrElement SVGFEGaussianBlurElement
instance IsRadioNodeListOrElement SVGFEFuncRElement
instance IsRadioNodeListOrElement SVGFEFuncGElement
instance IsRadioNodeListOrElement SVGFEFuncBElement
instance IsRadioNodeListOrElement SVGFEFuncAElement
instance IsRadioNodeListOrElement SVGFEFloodElement
instance IsRadioNodeListOrElement SVGFEDropShadowElement
instance IsRadioNodeListOrElement SVGFEDistantLightElement
instance IsRadioNodeListOrElement SVGFEDisplacementMapElement
instance IsRadioNodeListOrElement SVGFEDiffuseLightingElement
instance IsRadioNodeListOrElement SVGFEConvolveMatrixElement
instance IsRadioNodeListOrElement SVGFECompositeElement
instance IsRadioNodeListOrElement SVGFEComponentTransferElement
instance IsRadioNodeListOrElement SVGFEColorMatrixElement
instance IsRadioNodeListOrElement SVGFEBlendElement
instance IsRadioNodeListOrElement SVGEllipseElement
instance IsRadioNodeListOrElement SVGElement
instance IsRadioNodeListOrElement SVGDescElement
instance IsRadioNodeListOrElement SVGDefsElement
instance IsRadioNodeListOrElement SVGCursorElement
instance IsRadioNodeListOrElement SVGComponentTransferFunctionElement
instance IsRadioNodeListOrElement SVGClipPathElement
instance IsRadioNodeListOrElement SVGCircleElement
instance IsRadioNodeListOrElement SVGAnimationElement
instance IsRadioNodeListOrElement SVGAnimateTransformElement
instance IsRadioNodeListOrElement SVGAnimateMotionElement
instance IsRadioNodeListOrElement SVGAnimateElement
instance IsRadioNodeListOrElement SVGAnimateColorElement
instance IsRadioNodeListOrElement SVGAltGlyphItemElement
instance IsRadioNodeListOrElement SVGAltGlyphElement
instance IsRadioNodeListOrElement SVGAltGlyphDefElement
instance IsRadioNodeListOrElement SVGAElement
instance IsRadioNodeListOrElement HTMLVideoElement
instance IsRadioNodeListOrElement HTMLUnknownElement
instance IsRadioNodeListOrElement HTMLUListElement
instance IsRadioNodeListOrElement HTMLTrackElement
instance IsRadioNodeListOrElement HTMLTitleElement
instance IsRadioNodeListOrElement HTMLTimeElement
instance IsRadioNodeListOrElement HTMLTextAreaElement
instance IsRadioNodeListOrElement HTMLTemplateElement
instance IsRadioNodeListOrElement HTMLTableSectionElement
instance IsRadioNodeListOrElement HTMLTableRowElement
instance IsRadioNodeListOrElement HTMLTableElement
instance IsRadioNodeListOrElement HTMLTableColElement
instance IsRadioNodeListOrElement HTMLTableCellElement
instance IsRadioNodeListOrElement HTMLTableCaptionElement
instance IsRadioNodeListOrElement HTMLStyleElement
instance IsRadioNodeListOrElement HTMLSpanElement
instance IsRadioNodeListOrElement HTMLSourceElement
instance IsRadioNodeListOrElement HTMLSlotElement
instance IsRadioNodeListOrElement HTMLSelectElement
instance IsRadioNodeListOrElement HTMLScriptElement
instance IsRadioNodeListOrElement HTMLQuoteElement
instance IsRadioNodeListOrElement HTMLProgressElement
instance IsRadioNodeListOrElement HTMLPreElement
instance IsRadioNodeListOrElement HTMLPictureElement
instance IsRadioNodeListOrElement HTMLParamElement
instance IsRadioNodeListOrElement HTMLParagraphElement
instance IsRadioNodeListOrElement HTMLOutputElement
instance IsRadioNodeListOrElement HTMLOptionElement
instance IsRadioNodeListOrElement HTMLOptGroupElement
instance IsRadioNodeListOrElement HTMLObjectElement
instance IsRadioNodeListOrElement HTMLOListElement
instance IsRadioNodeListOrElement HTMLModElement
instance IsRadioNodeListOrElement HTMLMeterElement
instance IsRadioNodeListOrElement HTMLMetaElement
instance IsRadioNodeListOrElement HTMLMenuElement
instance IsRadioNodeListOrElement HTMLMediaElement
instance IsRadioNodeListOrElement HTMLMarqueeElement
instance IsRadioNodeListOrElement HTMLMapElement
instance IsRadioNodeListOrElement HTMLLinkElement
instance IsRadioNodeListOrElement HTMLLegendElement
instance IsRadioNodeListOrElement HTMLLabelElement
instance IsRadioNodeListOrElement HTMLLIElement
instance IsRadioNodeListOrElement HTMLKeygenElement
instance IsRadioNodeListOrElement HTMLInputElement
instance IsRadioNodeListOrElement HTMLImageElement
instance IsRadioNodeListOrElement HTMLIFrameElement
instance IsRadioNodeListOrElement HTMLHtmlElement
instance IsRadioNodeListOrElement HTMLHeadingElement
instance IsRadioNodeListOrElement HTMLHeadElement
instance IsRadioNodeListOrElement HTMLHRElement
instance IsRadioNodeListOrElement HTMLFrameSetElement
instance IsRadioNodeListOrElement HTMLFrameElement
instance IsRadioNodeListOrElement HTMLFormElement
instance IsRadioNodeListOrElement HTMLFontElement
instance IsRadioNodeListOrElement HTMLFieldSetElement
instance IsRadioNodeListOrElement HTMLEmbedElement
instance IsRadioNodeListOrElement HTMLElement
instance IsRadioNodeListOrElement HTMLDivElement
instance IsRadioNodeListOrElement HTMLDirectoryElement
instance IsRadioNodeListOrElement HTMLDetailsElement
instance IsRadioNodeListOrElement HTMLDataListElement
instance IsRadioNodeListOrElement HTMLDataElement
instance IsRadioNodeListOrElement HTMLDListElement
instance IsRadioNodeListOrElement HTMLCanvasElement
instance IsRadioNodeListOrElement HTMLButtonElement
instance IsRadioNodeListOrElement HTMLBodyElement
instance IsRadioNodeListOrElement HTMLBaseElement
instance IsRadioNodeListOrElement HTMLBRElement
instance IsRadioNodeListOrElement HTMLAudioElement
instance IsRadioNodeListOrElement HTMLAttachmentElement
instance IsRadioNodeListOrElement HTMLAreaElement
instance IsRadioNodeListOrElement HTMLAppletElement
instance IsRadioNodeListOrElement HTMLAnchorElement
instance IsRadioNodeListOrElement RadioNodeList
newtype RenderingContext = RenderingContext { unRenderingContext :: JSVal }
instance PToJSVal RenderingContext where
pToJSVal = unRenderingContext
{-# INLINE pToJSVal #-}
instance PFromJSVal RenderingContext where
pFromJSVal = RenderingContext
{-# INLINE pFromJSVal #-}
instance ToJSVal RenderingContext where
toJSVal = return . unRenderingContext
{-# INLINE toJSVal #-}
instance FromJSVal RenderingContext where
fromJSVal v = fmap RenderingContext <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RenderingContext
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RenderingContext where
makeObject = makeObject . unRenderingContext
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRenderingContext o
toRenderingContext :: IsRenderingContext o => o -> RenderingContext
toRenderingContext = RenderingContext . coerce
instance IsRenderingContext RenderingContext
instance IsRenderingContext WebGLRenderingContextBase
instance IsRenderingContext WebGLRenderingContext
instance IsRenderingContext WebGL2RenderingContext
instance IsRenderingContext CanvasRenderingContext2D
newtype SQLValue = SQLValue { unSQLValue :: JSVal }
instance PToJSVal SQLValue where
pToJSVal = unSQLValue
{-# INLINE pToJSVal #-}
instance PFromJSVal SQLValue where
pFromJSVal = SQLValue
{-# INLINE pFromJSVal #-}
instance ToJSVal SQLValue where
toJSVal = return . unSQLValue
{-# INLINE toJSVal #-}
instance FromJSVal SQLValue where
fromJSVal v = fmap SQLValue <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SQLValue
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SQLValue where
makeObject = makeObject . unSQLValue
class (FromJSVal o, ToJSVal o) => IsSQLValue o
instance IsSQLValue SQLValue
instance IsSQLValue (Maybe Text)
instance IsSQLValue (Maybe JSString)
instance IsSQLValue (Maybe String)
instance IsSQLValue Double
newtype StringOrArrayBuffer = StringOrArrayBuffer { unStringOrArrayBuffer :: JSVal }
instance PToJSVal StringOrArrayBuffer where
pToJSVal = unStringOrArrayBuffer
{-# INLINE pToJSVal #-}
instance PFromJSVal StringOrArrayBuffer where
pFromJSVal = StringOrArrayBuffer
{-# INLINE pFromJSVal #-}
instance ToJSVal StringOrArrayBuffer where
toJSVal = return . unStringOrArrayBuffer
{-# INLINE toJSVal #-}
instance FromJSVal StringOrArrayBuffer where
fromJSVal v = fmap StringOrArrayBuffer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . StringOrArrayBuffer
{-# INLINE fromJSValUnchecked #-}
instance MakeObject StringOrArrayBuffer where
makeObject = makeObject . unStringOrArrayBuffer
class (FromJSVal o, ToJSVal o) => IsStringOrArrayBuffer o
instance IsStringOrArrayBuffer StringOrArrayBuffer
instance IsStringOrArrayBuffer ArrayBuffer
instance IsStringOrArrayBuffer Text
instance IsStringOrArrayBuffer JSString
instance IsStringOrArrayBuffer String
newtype StringOrBinaryData = StringOrBinaryData { unStringOrBinaryData :: JSVal }
instance PToJSVal StringOrBinaryData where
pToJSVal = unStringOrBinaryData
{-# INLINE pToJSVal #-}
instance PFromJSVal StringOrBinaryData where
pFromJSVal = StringOrBinaryData
{-# INLINE pFromJSVal #-}
instance ToJSVal StringOrBinaryData where
toJSVal = return . unStringOrBinaryData
{-# INLINE toJSVal #-}
instance FromJSVal StringOrBinaryData where
fromJSVal v = fmap StringOrBinaryData <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . StringOrBinaryData
{-# INLINE fromJSValUnchecked #-}
instance MakeObject StringOrBinaryData where
makeObject = makeObject . unStringOrBinaryData
class (FromJSVal o, ToJSVal o) => IsStringOrBinaryData o
instance IsStringOrBinaryData StringOrBinaryData
instance IsStringOrBinaryData BinaryData
instance IsStringOrBinaryData BufferSource
instance IsStringOrBinaryData ArrayBufferView
instance IsStringOrBinaryData ArrayBuffer
instance IsStringOrBinaryData Text
instance IsStringOrBinaryData JSString
instance IsStringOrBinaryData String
newtype StringOrStrings = StringOrStrings { unStringOrStrings :: JSVal }
instance PToJSVal StringOrStrings where
pToJSVal = unStringOrStrings
{-# INLINE pToJSVal #-}
instance PFromJSVal StringOrStrings where
pFromJSVal = StringOrStrings
{-# INLINE pFromJSVal #-}
instance ToJSVal StringOrStrings where
toJSVal = return . unStringOrStrings
{-# INLINE toJSVal #-}
instance FromJSVal StringOrStrings where
fromJSVal v = fmap StringOrStrings <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . StringOrStrings
{-# INLINE fromJSValUnchecked #-}
instance MakeObject StringOrStrings where
makeObject = makeObject . unStringOrStrings
class (FromJSVal o, ToJSVal o) => IsStringOrStrings o
instance IsStringOrStrings StringOrStrings
instance IsStringOrStrings [Text]
instance IsStringOrStrings [JSString]
instance IsStringOrStrings [String]
instance IsStringOrStrings Text
instance IsStringOrStrings JSString
instance IsStringOrStrings String
newtype TexImageSource = TexImageSource { unTexImageSource :: JSVal }
instance PToJSVal TexImageSource where
pToJSVal = unTexImageSource
{-# INLINE pToJSVal #-}
instance PFromJSVal TexImageSource where
pFromJSVal = TexImageSource
{-# INLINE pFromJSVal #-}
instance ToJSVal TexImageSource where
toJSVal = return . unTexImageSource
{-# INLINE toJSVal #-}
instance FromJSVal TexImageSource where
fromJSVal v = fmap TexImageSource <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TexImageSource
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TexImageSource where
makeObject = makeObject . unTexImageSource
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsTexImageSource o
toTexImageSource :: IsTexImageSource o => o -> TexImageSource
toTexImageSource = TexImageSource . coerce
instance IsTexImageSource TexImageSource
instance IsTexImageSource ImageData
instance IsTexImageSource HTMLImageElement
instance IsTexImageSource HTMLVideoElement
instance IsTexImageSource HTMLCanvasElement
newtype Track = Track { unTrack :: JSVal }
instance PToJSVal Track where
pToJSVal = unTrack
{-# INLINE pToJSVal #-}
instance PFromJSVal Track where
pFromJSVal = Track
{-# INLINE pFromJSVal #-}
instance ToJSVal Track where
toJSVal = return . unTrack
{-# INLINE toJSVal #-}
instance FromJSVal Track where
fromJSVal v = fmap Track <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Track
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Track where
makeObject = makeObject . unTrack
class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsTrack o
toTrack :: IsTrack o => o -> Track
toTrack = Track . coerce
instance IsTrack Track
instance IsTrack TextTrack
instance IsTrack AudioTrack
instance IsTrack VideoTrack
newtype URLSearchParamsInit = URLSearchParamsInit { unURLSearchParamsInit :: JSVal }
instance PToJSVal URLSearchParamsInit where
pToJSVal = unURLSearchParamsInit
{-# INLINE pToJSVal #-}
instance PFromJSVal URLSearchParamsInit where
pFromJSVal = URLSearchParamsInit
{-# INLINE pFromJSVal #-}
instance ToJSVal URLSearchParamsInit where
toJSVal = return . unURLSearchParamsInit
{-# INLINE toJSVal #-}
instance FromJSVal URLSearchParamsInit where
fromJSVal v = fmap URLSearchParamsInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . URLSearchParamsInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject URLSearchParamsInit where
makeObject = makeObject . unURLSearchParamsInit
class (FromJSVal o, ToJSVal o) => IsURLSearchParamsInit o
instance IsURLSearchParamsInit URLSearchParamsInit
instance IsURLSearchParamsInit Text
instance IsURLSearchParamsInit JSString
instance IsURLSearchParamsInit String
instance IsURLSearchParamsInit [[Text]]
instance IsURLSearchParamsInit [[JSString]]
instance IsURLSearchParamsInit [[String]]
newtype XMLHttpRequestBody = XMLHttpRequestBody { unXMLHttpRequestBody :: JSVal }
instance PToJSVal XMLHttpRequestBody where
pToJSVal = unXMLHttpRequestBody
{-# INLINE pToJSVal #-}
instance PFromJSVal XMLHttpRequestBody where
pFromJSVal = XMLHttpRequestBody
{-# INLINE pFromJSVal #-}
instance ToJSVal XMLHttpRequestBody where
toJSVal = return . unXMLHttpRequestBody
{-# INLINE toJSVal #-}
instance FromJSVal XMLHttpRequestBody where
fromJSVal v = fmap XMLHttpRequestBody <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XMLHttpRequestBody
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XMLHttpRequestBody where
makeObject = makeObject . unXMLHttpRequestBody
class (FromJSVal o, ToJSVal o) => IsXMLHttpRequestBody o
instance IsXMLHttpRequestBody XMLHttpRequestBody
instance IsXMLHttpRequestBody BodyInit
instance IsXMLHttpRequestBody Blob
instance IsXMLHttpRequestBody BinaryData
instance IsXMLHttpRequestBody BufferSource
instance IsXMLHttpRequestBody ArrayBufferView
instance IsXMLHttpRequestBody ArrayBuffer
instance IsXMLHttpRequestBody FormData
instance IsXMLHttpRequestBody Text
instance IsXMLHttpRequestBody JSString
instance IsXMLHttpRequestBody String
instance IsXMLHttpRequestBody Document
instance IsXMLHttpRequestBody XMLDocument
instance IsXMLHttpRequestBody HTMLDocument
newtype ANGLEInstancedArrays = ANGLEInstancedArrays { unANGLEInstancedArrays :: JSVal }
instance PToJSVal ANGLEInstancedArrays where
pToJSVal = unANGLEInstancedArrays
{-# INLINE pToJSVal #-}
instance PFromJSVal ANGLEInstancedArrays where
pFromJSVal = ANGLEInstancedArrays
{-# INLINE pFromJSVal #-}
instance ToJSVal ANGLEInstancedArrays where
toJSVal = return . unANGLEInstancedArrays
{-# INLINE toJSVal #-}
instance FromJSVal ANGLEInstancedArrays where
fromJSVal v = fmap ANGLEInstancedArrays <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ANGLEInstancedArrays
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ANGLEInstancedArrays where
makeObject = makeObject . unANGLEInstancedArrays
instance IsGObject ANGLEInstancedArrays where
typeGType _ = gTypeANGLEInstancedArrays
{-# INLINE typeGType #-}
noANGLEInstancedArrays :: Maybe ANGLEInstancedArrays
noANGLEInstancedArrays = Nothing
{-# INLINE noANGLEInstancedArrays #-}
gTypeANGLEInstancedArrays :: JSM GType
gTypeANGLEInstancedArrays = GType . Object <$> jsg "ANGLEInstancedArrays"
newtype AbstractWorker = AbstractWorker { unAbstractWorker :: JSVal }
instance PToJSVal AbstractWorker where
pToJSVal = unAbstractWorker
{-# INLINE pToJSVal #-}
instance PFromJSVal AbstractWorker where
pFromJSVal = AbstractWorker
{-# INLINE pFromJSVal #-}
instance ToJSVal AbstractWorker where
toJSVal = return . unAbstractWorker
{-# INLINE toJSVal #-}
instance FromJSVal AbstractWorker where
fromJSVal v = fmap AbstractWorker <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AbstractWorker
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AbstractWorker where
makeObject = makeObject . unAbstractWorker
class (IsGObject o) => IsAbstractWorker o
toAbstractWorker :: IsAbstractWorker o => o -> AbstractWorker
toAbstractWorker = AbstractWorker . coerce
instance IsAbstractWorker AbstractWorker
instance IsGObject AbstractWorker where
typeGType _ = gTypeAbstractWorker
{-# INLINE typeGType #-}
noAbstractWorker :: Maybe AbstractWorker
noAbstractWorker = Nothing
{-# INLINE noAbstractWorker #-}
gTypeAbstractWorker :: JSM GType
gTypeAbstractWorker = GType . Object <$> jsg "AbstractWorker"
newtype Acceleration = Acceleration { unAcceleration :: JSVal }
instance PToJSVal Acceleration where
pToJSVal = unAcceleration
{-# INLINE pToJSVal #-}
instance PFromJSVal Acceleration where
pFromJSVal = Acceleration
{-# INLINE pFromJSVal #-}
instance ToJSVal Acceleration where
toJSVal = return . unAcceleration
{-# INLINE toJSVal #-}
instance FromJSVal Acceleration where
fromJSVal v = fmap Acceleration <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Acceleration
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Acceleration where
makeObject = makeObject . unAcceleration
instance IsGObject Acceleration where
typeGType _ = gTypeAcceleration
{-# INLINE typeGType #-}
noAcceleration :: Maybe Acceleration
noAcceleration = Nothing
{-# INLINE noAcceleration #-}
gTypeAcceleration :: JSM GType
gTypeAcceleration = GType . Object <$> jsg "Acceleration"
newtype AddEventListenerOptions = AddEventListenerOptions { unAddEventListenerOptions :: JSVal }
instance PToJSVal AddEventListenerOptions where
pToJSVal = unAddEventListenerOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal AddEventListenerOptions where
pFromJSVal = AddEventListenerOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal AddEventListenerOptions where
toJSVal = return . unAddEventListenerOptions
{-# INLINE toJSVal #-}
instance FromJSVal AddEventListenerOptions where
fromJSVal v = fmap AddEventListenerOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AddEventListenerOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AddEventListenerOptions where
makeObject = makeObject . unAddEventListenerOptions
instance IsEventListenerOptions AddEventListenerOptions
instance IsGObject AddEventListenerOptions where
typeGType _ = gTypeAddEventListenerOptions
{-# INLINE typeGType #-}
noAddEventListenerOptions :: Maybe AddEventListenerOptions
noAddEventListenerOptions = Nothing
{-# INLINE noAddEventListenerOptions #-}
gTypeAddEventListenerOptions :: JSM GType
gTypeAddEventListenerOptions = GType . Object <$> jsg "AddEventListenerOptions"
newtype AesCbcCfbParams = AesCbcCfbParams { unAesCbcCfbParams :: JSVal }
instance PToJSVal AesCbcCfbParams where
pToJSVal = unAesCbcCfbParams
{-# INLINE pToJSVal #-}
instance PFromJSVal AesCbcCfbParams where
pFromJSVal = AesCbcCfbParams
{-# INLINE pFromJSVal #-}
instance ToJSVal AesCbcCfbParams where
toJSVal = return . unAesCbcCfbParams
{-# INLINE toJSVal #-}
instance FromJSVal AesCbcCfbParams where
fromJSVal v = fmap AesCbcCfbParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AesCbcCfbParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AesCbcCfbParams where
makeObject = makeObject . unAesCbcCfbParams
instance IsCryptoAlgorithmParameters AesCbcCfbParams
instance IsGObject AesCbcCfbParams where
typeGType _ = gTypeAesCbcCfbParams
{-# INLINE typeGType #-}
noAesCbcCfbParams :: Maybe AesCbcCfbParams
noAesCbcCfbParams = Nothing
{-# INLINE noAesCbcCfbParams #-}
gTypeAesCbcCfbParams :: JSM GType
gTypeAesCbcCfbParams = GType . Object <$> jsg "AesCbcCfbParams"
newtype AesCtrParams = AesCtrParams { unAesCtrParams :: JSVal }
instance PToJSVal AesCtrParams where
pToJSVal = unAesCtrParams
{-# INLINE pToJSVal #-}
instance PFromJSVal AesCtrParams where
pFromJSVal = AesCtrParams
{-# INLINE pFromJSVal #-}
instance ToJSVal AesCtrParams where
toJSVal = return . unAesCtrParams
{-# INLINE toJSVal #-}
instance FromJSVal AesCtrParams where
fromJSVal v = fmap AesCtrParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AesCtrParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AesCtrParams where
makeObject = makeObject . unAesCtrParams
instance IsCryptoAlgorithmParameters AesCtrParams
instance IsGObject AesCtrParams where
typeGType _ = gTypeAesCtrParams
{-# INLINE typeGType #-}
noAesCtrParams :: Maybe AesCtrParams
noAesCtrParams = Nothing
{-# INLINE noAesCtrParams #-}
gTypeAesCtrParams :: JSM GType
gTypeAesCtrParams = GType . Object <$> jsg "AesCtrParams"
newtype AesGcmParams = AesGcmParams { unAesGcmParams :: JSVal }
instance PToJSVal AesGcmParams where
pToJSVal = unAesGcmParams
{-# INLINE pToJSVal #-}
instance PFromJSVal AesGcmParams where
pFromJSVal = AesGcmParams
{-# INLINE pFromJSVal #-}
instance ToJSVal AesGcmParams where
toJSVal = return . unAesGcmParams
{-# INLINE toJSVal #-}
instance FromJSVal AesGcmParams where
fromJSVal v = fmap AesGcmParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AesGcmParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AesGcmParams where
makeObject = makeObject . unAesGcmParams
instance IsCryptoAlgorithmParameters AesGcmParams
instance IsGObject AesGcmParams where
typeGType _ = gTypeAesGcmParams
{-# INLINE typeGType #-}
noAesGcmParams :: Maybe AesGcmParams
noAesGcmParams = Nothing
{-# INLINE noAesGcmParams #-}
gTypeAesGcmParams :: JSM GType
gTypeAesGcmParams = GType . Object <$> jsg "AesGcmParams"
newtype AesKeyParams = AesKeyParams { unAesKeyParams :: JSVal }
instance PToJSVal AesKeyParams where
pToJSVal = unAesKeyParams
{-# INLINE pToJSVal #-}
instance PFromJSVal AesKeyParams where
pFromJSVal = AesKeyParams
{-# INLINE pFromJSVal #-}
instance ToJSVal AesKeyParams where
toJSVal = return . unAesKeyParams
{-# INLINE toJSVal #-}
instance FromJSVal AesKeyParams where
fromJSVal v = fmap AesKeyParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AesKeyParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AesKeyParams where
makeObject = makeObject . unAesKeyParams
instance IsCryptoAlgorithmParameters AesKeyParams
instance IsGObject AesKeyParams where
typeGType _ = gTypeAesKeyParams
{-# INLINE typeGType #-}
noAesKeyParams :: Maybe AesKeyParams
noAesKeyParams = Nothing
{-# INLINE noAesKeyParams #-}
gTypeAesKeyParams :: JSM GType
gTypeAesKeyParams = GType . Object <$> jsg "AesKeyParams"
newtype AnalyserNode = AnalyserNode { unAnalyserNode :: JSVal }
instance PToJSVal AnalyserNode where
pToJSVal = unAnalyserNode
{-# INLINE pToJSVal #-}
instance PFromJSVal AnalyserNode where
pFromJSVal = AnalyserNode
{-# INLINE pFromJSVal #-}
instance ToJSVal AnalyserNode where
toJSVal = return . unAnalyserNode
{-# INLINE toJSVal #-}
instance FromJSVal AnalyserNode where
fromJSVal v = fmap AnalyserNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AnalyserNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AnalyserNode where
makeObject = makeObject . unAnalyserNode
instance IsAudioNode AnalyserNode
instance IsEventTarget AnalyserNode
instance IsGObject AnalyserNode where
typeGType _ = gTypeAnalyserNode
{-# INLINE typeGType #-}
noAnalyserNode :: Maybe AnalyserNode
noAnalyserNode = Nothing
{-# INLINE noAnalyserNode #-}
gTypeAnalyserNode :: JSM GType
gTypeAnalyserNode = GType . Object <$> jsg "AnalyserNode"
newtype Animatable = Animatable { unAnimatable :: JSVal }
instance PToJSVal Animatable where
pToJSVal = unAnimatable
{-# INLINE pToJSVal #-}
instance PFromJSVal Animatable where
pFromJSVal = Animatable
{-# INLINE pFromJSVal #-}
instance ToJSVal Animatable where
toJSVal = return . unAnimatable
{-# INLINE toJSVal #-}
instance FromJSVal Animatable where
fromJSVal v = fmap Animatable <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Animatable
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Animatable where
makeObject = makeObject . unAnimatable
class (IsGObject o) => IsAnimatable o
toAnimatable :: IsAnimatable o => o -> Animatable
toAnimatable = Animatable . coerce
instance IsAnimatable Animatable
instance IsGObject Animatable where
typeGType _ = gTypeAnimatable
{-# INLINE typeGType #-}
noAnimatable :: Maybe Animatable
noAnimatable = Nothing
{-# INLINE noAnimatable #-}
gTypeAnimatable :: JSM GType
gTypeAnimatable = GType . Object <$> jsg "Animatable"
newtype Animation = Animation { unAnimation :: JSVal }
instance PToJSVal Animation where
pToJSVal = unAnimation
{-# INLINE pToJSVal #-}
instance PFromJSVal Animation where
pFromJSVal = Animation
{-# INLINE pFromJSVal #-}
instance ToJSVal Animation where
toJSVal = return . unAnimation
{-# INLINE toJSVal #-}
instance FromJSVal Animation where
fromJSVal v = fmap Animation <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Animation
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Animation where
makeObject = makeObject . unAnimation
instance IsGObject Animation where
typeGType _ = gTypeAnimation
{-# INLINE typeGType #-}
noAnimation :: Maybe Animation
noAnimation = Nothing
{-# INLINE noAnimation #-}
gTypeAnimation :: JSM GType
gTypeAnimation = GType . Object <$> jsg "Animation"
newtype AnimationEffect = AnimationEffect { unAnimationEffect :: JSVal }
instance PToJSVal AnimationEffect where
pToJSVal = unAnimationEffect
{-# INLINE pToJSVal #-}
instance PFromJSVal AnimationEffect where
pFromJSVal = AnimationEffect
{-# INLINE pFromJSVal #-}
instance ToJSVal AnimationEffect where
toJSVal = return . unAnimationEffect
{-# INLINE toJSVal #-}
instance FromJSVal AnimationEffect where
fromJSVal v = fmap AnimationEffect <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AnimationEffect
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AnimationEffect where
makeObject = makeObject . unAnimationEffect
class (IsGObject o) => IsAnimationEffect o
toAnimationEffect :: IsAnimationEffect o => o -> AnimationEffect
toAnimationEffect = AnimationEffect . coerce
instance IsAnimationEffect AnimationEffect
instance IsGObject AnimationEffect where
typeGType _ = gTypeAnimationEffect
{-# INLINE typeGType #-}
noAnimationEffect :: Maybe AnimationEffect
noAnimationEffect = Nothing
{-# INLINE noAnimationEffect #-}
gTypeAnimationEffect :: JSM GType
gTypeAnimationEffect = GType . Object <$> jsg "AnimationEffect"
newtype AnimationEvent = AnimationEvent { unAnimationEvent :: JSVal }
instance PToJSVal AnimationEvent where
pToJSVal = unAnimationEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal AnimationEvent where
pFromJSVal = AnimationEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal AnimationEvent where
toJSVal = return . unAnimationEvent
{-# INLINE toJSVal #-}
instance FromJSVal AnimationEvent where
fromJSVal v = fmap AnimationEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AnimationEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AnimationEvent where
makeObject = makeObject . unAnimationEvent
instance IsEvent AnimationEvent
instance IsGObject AnimationEvent where
typeGType _ = gTypeAnimationEvent
{-# INLINE typeGType #-}
noAnimationEvent :: Maybe AnimationEvent
noAnimationEvent = Nothing
{-# INLINE noAnimationEvent #-}
gTypeAnimationEvent :: JSM GType
gTypeAnimationEvent = GType . Object <$> jsg "AnimationEvent"
newtype AnimationEventInit = AnimationEventInit { unAnimationEventInit :: JSVal }
instance PToJSVal AnimationEventInit where
pToJSVal = unAnimationEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal AnimationEventInit where
pFromJSVal = AnimationEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal AnimationEventInit where
toJSVal = return . unAnimationEventInit
{-# INLINE toJSVal #-}
instance FromJSVal AnimationEventInit where
fromJSVal v = fmap AnimationEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AnimationEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AnimationEventInit where
makeObject = makeObject . unAnimationEventInit
instance IsEventInit AnimationEventInit
instance IsGObject AnimationEventInit where
typeGType _ = gTypeAnimationEventInit
{-# INLINE typeGType #-}
noAnimationEventInit :: Maybe AnimationEventInit
noAnimationEventInit = Nothing
{-# INLINE noAnimationEventInit #-}
gTypeAnimationEventInit :: JSM GType
gTypeAnimationEventInit = GType . Object <$> jsg "AnimationEventInit"
newtype AnimationTimeline = AnimationTimeline { unAnimationTimeline :: JSVal }
instance PToJSVal AnimationTimeline where
pToJSVal = unAnimationTimeline
{-# INLINE pToJSVal #-}
instance PFromJSVal AnimationTimeline where
pFromJSVal = AnimationTimeline
{-# INLINE pFromJSVal #-}
instance ToJSVal AnimationTimeline where
toJSVal = return . unAnimationTimeline
{-# INLINE toJSVal #-}
instance FromJSVal AnimationTimeline where
fromJSVal v = fmap AnimationTimeline <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AnimationTimeline
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AnimationTimeline where
makeObject = makeObject . unAnimationTimeline
class (IsGObject o) => IsAnimationTimeline o
toAnimationTimeline :: IsAnimationTimeline o => o -> AnimationTimeline
toAnimationTimeline = AnimationTimeline . coerce
instance IsAnimationTimeline AnimationTimeline
instance IsGObject AnimationTimeline where
typeGType _ = gTypeAnimationTimeline
{-# INLINE typeGType #-}
noAnimationTimeline :: Maybe AnimationTimeline
noAnimationTimeline = Nothing
{-# INLINE noAnimationTimeline #-}
gTypeAnimationTimeline :: JSM GType
gTypeAnimationTimeline = GType . Object <$> jsg "AnimationTimeline"
newtype ApplePayError = ApplePayError { unApplePayError :: JSVal }
instance PToJSVal ApplePayError where
pToJSVal = unApplePayError
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayError where
pFromJSVal = ApplePayError
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayError where
toJSVal = return . unApplePayError
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayError where
fromJSVal v = fmap ApplePayError <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayError
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayError where
makeObject = makeObject . unApplePayError
instance IsGObject ApplePayError where
typeGType _ = gTypeApplePayError
{-# INLINE typeGType #-}
noApplePayError :: Maybe ApplePayError
noApplePayError = Nothing
{-# INLINE noApplePayError #-}
gTypeApplePayError :: JSM GType
gTypeApplePayError = GType . Object <$> jsg "ApplePayError"
newtype ApplePayLineItem = ApplePayLineItem { unApplePayLineItem :: JSVal }
instance PToJSVal ApplePayLineItem where
pToJSVal = unApplePayLineItem
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayLineItem where
pFromJSVal = ApplePayLineItem
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayLineItem where
toJSVal = return . unApplePayLineItem
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayLineItem where
fromJSVal v = fmap ApplePayLineItem <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayLineItem
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayLineItem where
makeObject = makeObject . unApplePayLineItem
instance IsGObject ApplePayLineItem where
typeGType _ = gTypeApplePayLineItem
{-# INLINE typeGType #-}
noApplePayLineItem :: Maybe ApplePayLineItem
noApplePayLineItem = Nothing
{-# INLINE noApplePayLineItem #-}
gTypeApplePayLineItem :: JSM GType
gTypeApplePayLineItem = GType . Object <$> jsg "ApplePayLineItem"
newtype ApplePayPayment = ApplePayPayment { unApplePayPayment :: JSVal }
instance PToJSVal ApplePayPayment where
pToJSVal = unApplePayPayment
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayPayment where
pFromJSVal = ApplePayPayment
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayPayment where
toJSVal = return . unApplePayPayment
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayPayment where
fromJSVal v = fmap ApplePayPayment <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayPayment
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayPayment where
makeObject = makeObject . unApplePayPayment
instance IsGObject ApplePayPayment where
typeGType _ = gTypeApplePayPayment
{-# INLINE typeGType #-}
noApplePayPayment :: Maybe ApplePayPayment
noApplePayPayment = Nothing
{-# INLINE noApplePayPayment #-}
gTypeApplePayPayment :: JSM GType
gTypeApplePayPayment = GType . Object <$> jsg "ApplePayPayment"
newtype ApplePayPaymentAuthorizationResult = ApplePayPaymentAuthorizationResult { unApplePayPaymentAuthorizationResult :: JSVal }
instance PToJSVal ApplePayPaymentAuthorizationResult where
pToJSVal = unApplePayPaymentAuthorizationResult
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayPaymentAuthorizationResult where
pFromJSVal = ApplePayPaymentAuthorizationResult
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayPaymentAuthorizationResult where
toJSVal = return . unApplePayPaymentAuthorizationResult
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayPaymentAuthorizationResult where
fromJSVal v = fmap ApplePayPaymentAuthorizationResult <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayPaymentAuthorizationResult
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayPaymentAuthorizationResult where
makeObject = makeObject . unApplePayPaymentAuthorizationResult
instance IsGObject ApplePayPaymentAuthorizationResult where
typeGType _ = gTypeApplePayPaymentAuthorizationResult
{-# INLINE typeGType #-}
noApplePayPaymentAuthorizationResult :: Maybe ApplePayPaymentAuthorizationResult
noApplePayPaymentAuthorizationResult = Nothing
{-# INLINE noApplePayPaymentAuthorizationResult #-}
gTypeApplePayPaymentAuthorizationResult :: JSM GType
gTypeApplePayPaymentAuthorizationResult = GType . Object <$> jsg "ApplePayPaymentAuthorizationResult"
newtype ApplePayPaymentAuthorizedEvent = ApplePayPaymentAuthorizedEvent { unApplePayPaymentAuthorizedEvent :: JSVal }
instance PToJSVal ApplePayPaymentAuthorizedEvent where
pToJSVal = unApplePayPaymentAuthorizedEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayPaymentAuthorizedEvent where
pFromJSVal = ApplePayPaymentAuthorizedEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayPaymentAuthorizedEvent where
toJSVal = return . unApplePayPaymentAuthorizedEvent
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayPaymentAuthorizedEvent where
fromJSVal v = fmap ApplePayPaymentAuthorizedEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayPaymentAuthorizedEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayPaymentAuthorizedEvent where
makeObject = makeObject . unApplePayPaymentAuthorizedEvent
instance IsEvent ApplePayPaymentAuthorizedEvent
instance IsGObject ApplePayPaymentAuthorizedEvent where
typeGType _ = gTypeApplePayPaymentAuthorizedEvent
{-# INLINE typeGType #-}
noApplePayPaymentAuthorizedEvent :: Maybe ApplePayPaymentAuthorizedEvent
noApplePayPaymentAuthorizedEvent = Nothing
{-# INLINE noApplePayPaymentAuthorizedEvent #-}
gTypeApplePayPaymentAuthorizedEvent :: JSM GType
gTypeApplePayPaymentAuthorizedEvent = GType . Object <$> jsg "ApplePayPaymentAuthorizedEvent"
newtype ApplePayPaymentContact = ApplePayPaymentContact { unApplePayPaymentContact :: JSVal }
instance PToJSVal ApplePayPaymentContact where
pToJSVal = unApplePayPaymentContact
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayPaymentContact where
pFromJSVal = ApplePayPaymentContact
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayPaymentContact where
toJSVal = return . unApplePayPaymentContact
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayPaymentContact where
fromJSVal v = fmap ApplePayPaymentContact <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayPaymentContact
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayPaymentContact where
makeObject = makeObject . unApplePayPaymentContact
instance IsGObject ApplePayPaymentContact where
typeGType _ = gTypeApplePayPaymentContact
{-# INLINE typeGType #-}
noApplePayPaymentContact :: Maybe ApplePayPaymentContact
noApplePayPaymentContact = Nothing
{-# INLINE noApplePayPaymentContact #-}
gTypeApplePayPaymentContact :: JSM GType
gTypeApplePayPaymentContact = GType . Object <$> jsg "ApplePayPaymentContact"
newtype ApplePayPaymentMethod = ApplePayPaymentMethod { unApplePayPaymentMethod :: JSVal }
instance PToJSVal ApplePayPaymentMethod where
pToJSVal = unApplePayPaymentMethod
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayPaymentMethod where
pFromJSVal = ApplePayPaymentMethod
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayPaymentMethod where
toJSVal = return . unApplePayPaymentMethod
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayPaymentMethod where
fromJSVal v = fmap ApplePayPaymentMethod <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayPaymentMethod
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayPaymentMethod where
makeObject = makeObject . unApplePayPaymentMethod
instance IsGObject ApplePayPaymentMethod where
typeGType _ = gTypeApplePayPaymentMethod
{-# INLINE typeGType #-}
noApplePayPaymentMethod :: Maybe ApplePayPaymentMethod
noApplePayPaymentMethod = Nothing
{-# INLINE noApplePayPaymentMethod #-}
gTypeApplePayPaymentMethod :: JSM GType
gTypeApplePayPaymentMethod = GType . Object <$> jsg "ApplePayPaymentMethod"
newtype ApplePayPaymentMethodSelectedEvent = ApplePayPaymentMethodSelectedEvent { unApplePayPaymentMethodSelectedEvent :: JSVal }
instance PToJSVal ApplePayPaymentMethodSelectedEvent where
pToJSVal = unApplePayPaymentMethodSelectedEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayPaymentMethodSelectedEvent where
pFromJSVal = ApplePayPaymentMethodSelectedEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayPaymentMethodSelectedEvent where
toJSVal = return . unApplePayPaymentMethodSelectedEvent
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayPaymentMethodSelectedEvent where
fromJSVal v = fmap ApplePayPaymentMethodSelectedEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayPaymentMethodSelectedEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayPaymentMethodSelectedEvent where
makeObject = makeObject . unApplePayPaymentMethodSelectedEvent
instance IsEvent ApplePayPaymentMethodSelectedEvent
instance IsGObject ApplePayPaymentMethodSelectedEvent where
typeGType _ = gTypeApplePayPaymentMethodSelectedEvent
{-# INLINE typeGType #-}
noApplePayPaymentMethodSelectedEvent :: Maybe ApplePayPaymentMethodSelectedEvent
noApplePayPaymentMethodSelectedEvent = Nothing
{-# INLINE noApplePayPaymentMethodSelectedEvent #-}
gTypeApplePayPaymentMethodSelectedEvent :: JSM GType
gTypeApplePayPaymentMethodSelectedEvent = GType . Object <$> jsg "ApplePayPaymentMethodSelectedEvent"
newtype ApplePayPaymentMethodUpdate = ApplePayPaymentMethodUpdate { unApplePayPaymentMethodUpdate :: JSVal }
instance PToJSVal ApplePayPaymentMethodUpdate where
pToJSVal = unApplePayPaymentMethodUpdate
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayPaymentMethodUpdate where
pFromJSVal = ApplePayPaymentMethodUpdate
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayPaymentMethodUpdate where
toJSVal = return . unApplePayPaymentMethodUpdate
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayPaymentMethodUpdate where
fromJSVal v = fmap ApplePayPaymentMethodUpdate <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayPaymentMethodUpdate
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayPaymentMethodUpdate where
makeObject = makeObject . unApplePayPaymentMethodUpdate
instance IsGObject ApplePayPaymentMethodUpdate where
typeGType _ = gTypeApplePayPaymentMethodUpdate
{-# INLINE typeGType #-}
noApplePayPaymentMethodUpdate :: Maybe ApplePayPaymentMethodUpdate
noApplePayPaymentMethodUpdate = Nothing
{-# INLINE noApplePayPaymentMethodUpdate #-}
gTypeApplePayPaymentMethodUpdate :: JSM GType
gTypeApplePayPaymentMethodUpdate = GType . Object <$> jsg "ApplePayPaymentMethodUpdate"
newtype ApplePayPaymentPass = ApplePayPaymentPass { unApplePayPaymentPass :: JSVal }
instance PToJSVal ApplePayPaymentPass where
pToJSVal = unApplePayPaymentPass
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayPaymentPass where
pFromJSVal = ApplePayPaymentPass
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayPaymentPass where
toJSVal = return . unApplePayPaymentPass
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayPaymentPass where
fromJSVal v = fmap ApplePayPaymentPass <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayPaymentPass
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayPaymentPass where
makeObject = makeObject . unApplePayPaymentPass
instance IsGObject ApplePayPaymentPass where
typeGType _ = gTypeApplePayPaymentPass
{-# INLINE typeGType #-}
noApplePayPaymentPass :: Maybe ApplePayPaymentPass
noApplePayPaymentPass = Nothing
{-# INLINE noApplePayPaymentPass #-}
gTypeApplePayPaymentPass :: JSM GType
gTypeApplePayPaymentPass = GType . Object <$> jsg "ApplePayPaymentPass"
newtype ApplePayPaymentRequest = ApplePayPaymentRequest { unApplePayPaymentRequest :: JSVal }
instance PToJSVal ApplePayPaymentRequest where
pToJSVal = unApplePayPaymentRequest
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayPaymentRequest where
pFromJSVal = ApplePayPaymentRequest
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayPaymentRequest where
toJSVal = return . unApplePayPaymentRequest
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayPaymentRequest where
fromJSVal v = fmap ApplePayPaymentRequest <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayPaymentRequest
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayPaymentRequest where
makeObject = makeObject . unApplePayPaymentRequest
instance IsGObject ApplePayPaymentRequest where
typeGType _ = gTypeApplePayPaymentRequest
{-# INLINE typeGType #-}
noApplePayPaymentRequest :: Maybe ApplePayPaymentRequest
noApplePayPaymentRequest = Nothing
{-# INLINE noApplePayPaymentRequest #-}
gTypeApplePayPaymentRequest :: JSM GType
gTypeApplePayPaymentRequest = GType . Object <$> jsg "ApplePayPaymentRequest"
newtype ApplePayPaymentToken = ApplePayPaymentToken { unApplePayPaymentToken :: JSVal }
instance PToJSVal ApplePayPaymentToken where
pToJSVal = unApplePayPaymentToken
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayPaymentToken where
pFromJSVal = ApplePayPaymentToken
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayPaymentToken where
toJSVal = return . unApplePayPaymentToken
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayPaymentToken where
fromJSVal v = fmap ApplePayPaymentToken <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayPaymentToken
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayPaymentToken where
makeObject = makeObject . unApplePayPaymentToken
instance IsGObject ApplePayPaymentToken where
typeGType _ = gTypeApplePayPaymentToken
{-# INLINE typeGType #-}
noApplePayPaymentToken :: Maybe ApplePayPaymentToken
noApplePayPaymentToken = Nothing
{-# INLINE noApplePayPaymentToken #-}
gTypeApplePayPaymentToken :: JSM GType
gTypeApplePayPaymentToken = GType . Object <$> jsg "ApplePayPaymentToken"
newtype ApplePaySession = ApplePaySession { unApplePaySession :: JSVal }
instance PToJSVal ApplePaySession where
pToJSVal = unApplePaySession
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePaySession where
pFromJSVal = ApplePaySession
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePaySession where
toJSVal = return . unApplePaySession
{-# INLINE toJSVal #-}
instance FromJSVal ApplePaySession where
fromJSVal v = fmap ApplePaySession <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePaySession
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePaySession where
makeObject = makeObject . unApplePaySession
instance IsEventTarget ApplePaySession
instance IsGObject ApplePaySession where
typeGType _ = gTypeApplePaySession
{-# INLINE typeGType #-}
noApplePaySession :: Maybe ApplePaySession
noApplePaySession = Nothing
{-# INLINE noApplePaySession #-}
gTypeApplePaySession :: JSM GType
gTypeApplePaySession = GType . Object <$> jsg "ApplePaySession"
newtype ApplePayShippingContactSelectedEvent = ApplePayShippingContactSelectedEvent { unApplePayShippingContactSelectedEvent :: JSVal }
instance PToJSVal ApplePayShippingContactSelectedEvent where
pToJSVal = unApplePayShippingContactSelectedEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayShippingContactSelectedEvent where
pFromJSVal = ApplePayShippingContactSelectedEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayShippingContactSelectedEvent where
toJSVal = return . unApplePayShippingContactSelectedEvent
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayShippingContactSelectedEvent where
fromJSVal v = fmap ApplePayShippingContactSelectedEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayShippingContactSelectedEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayShippingContactSelectedEvent where
makeObject = makeObject . unApplePayShippingContactSelectedEvent
instance IsEvent ApplePayShippingContactSelectedEvent
instance IsGObject ApplePayShippingContactSelectedEvent where
typeGType _ = gTypeApplePayShippingContactSelectedEvent
{-# INLINE typeGType #-}
noApplePayShippingContactSelectedEvent :: Maybe ApplePayShippingContactSelectedEvent
noApplePayShippingContactSelectedEvent = Nothing
{-# INLINE noApplePayShippingContactSelectedEvent #-}
gTypeApplePayShippingContactSelectedEvent :: JSM GType
gTypeApplePayShippingContactSelectedEvent = GType . Object <$> jsg "ApplePayShippingContactSelectedEvent"
newtype ApplePayShippingContactUpdate = ApplePayShippingContactUpdate { unApplePayShippingContactUpdate :: JSVal }
instance PToJSVal ApplePayShippingContactUpdate where
pToJSVal = unApplePayShippingContactUpdate
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayShippingContactUpdate where
pFromJSVal = ApplePayShippingContactUpdate
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayShippingContactUpdate where
toJSVal = return . unApplePayShippingContactUpdate
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayShippingContactUpdate where
fromJSVal v = fmap ApplePayShippingContactUpdate <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayShippingContactUpdate
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayShippingContactUpdate where
makeObject = makeObject . unApplePayShippingContactUpdate
instance IsGObject ApplePayShippingContactUpdate where
typeGType _ = gTypeApplePayShippingContactUpdate
{-# INLINE typeGType #-}
noApplePayShippingContactUpdate :: Maybe ApplePayShippingContactUpdate
noApplePayShippingContactUpdate = Nothing
{-# INLINE noApplePayShippingContactUpdate #-}
gTypeApplePayShippingContactUpdate :: JSM GType
gTypeApplePayShippingContactUpdate = GType . Object <$> jsg "ApplePayShippingContactUpdate"
newtype ApplePayShippingMethod = ApplePayShippingMethod { unApplePayShippingMethod :: JSVal }
instance PToJSVal ApplePayShippingMethod where
pToJSVal = unApplePayShippingMethod
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayShippingMethod where
pFromJSVal = ApplePayShippingMethod
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayShippingMethod where
toJSVal = return . unApplePayShippingMethod
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayShippingMethod where
fromJSVal v = fmap ApplePayShippingMethod <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayShippingMethod
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayShippingMethod where
makeObject = makeObject . unApplePayShippingMethod
instance IsGObject ApplePayShippingMethod where
typeGType _ = gTypeApplePayShippingMethod
{-# INLINE typeGType #-}
noApplePayShippingMethod :: Maybe ApplePayShippingMethod
noApplePayShippingMethod = Nothing
{-# INLINE noApplePayShippingMethod #-}
gTypeApplePayShippingMethod :: JSM GType
gTypeApplePayShippingMethod = GType . Object <$> jsg "ApplePayShippingMethod"
newtype ApplePayShippingMethodSelectedEvent = ApplePayShippingMethodSelectedEvent { unApplePayShippingMethodSelectedEvent :: JSVal }
instance PToJSVal ApplePayShippingMethodSelectedEvent where
pToJSVal = unApplePayShippingMethodSelectedEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayShippingMethodSelectedEvent where
pFromJSVal = ApplePayShippingMethodSelectedEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayShippingMethodSelectedEvent where
toJSVal = return . unApplePayShippingMethodSelectedEvent
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayShippingMethodSelectedEvent where
fromJSVal v = fmap ApplePayShippingMethodSelectedEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayShippingMethodSelectedEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayShippingMethodSelectedEvent where
makeObject = makeObject . unApplePayShippingMethodSelectedEvent
instance IsEvent ApplePayShippingMethodSelectedEvent
instance IsGObject ApplePayShippingMethodSelectedEvent where
typeGType _ = gTypeApplePayShippingMethodSelectedEvent
{-# INLINE typeGType #-}
noApplePayShippingMethodSelectedEvent :: Maybe ApplePayShippingMethodSelectedEvent
noApplePayShippingMethodSelectedEvent = Nothing
{-# INLINE noApplePayShippingMethodSelectedEvent #-}
gTypeApplePayShippingMethodSelectedEvent :: JSM GType
gTypeApplePayShippingMethodSelectedEvent = GType . Object <$> jsg "ApplePayShippingMethodSelectedEvent"
newtype ApplePayShippingMethodUpdate = ApplePayShippingMethodUpdate { unApplePayShippingMethodUpdate :: JSVal }
instance PToJSVal ApplePayShippingMethodUpdate where
pToJSVal = unApplePayShippingMethodUpdate
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayShippingMethodUpdate where
pFromJSVal = ApplePayShippingMethodUpdate
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayShippingMethodUpdate where
toJSVal = return . unApplePayShippingMethodUpdate
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayShippingMethodUpdate where
fromJSVal v = fmap ApplePayShippingMethodUpdate <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayShippingMethodUpdate
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayShippingMethodUpdate where
makeObject = makeObject . unApplePayShippingMethodUpdate
instance IsGObject ApplePayShippingMethodUpdate where
typeGType _ = gTypeApplePayShippingMethodUpdate
{-# INLINE typeGType #-}
noApplePayShippingMethodUpdate :: Maybe ApplePayShippingMethodUpdate
noApplePayShippingMethodUpdate = Nothing
{-# INLINE noApplePayShippingMethodUpdate #-}
gTypeApplePayShippingMethodUpdate :: JSM GType
gTypeApplePayShippingMethodUpdate = GType . Object <$> jsg "ApplePayShippingMethodUpdate"
newtype ApplePayValidateMerchantEvent = ApplePayValidateMerchantEvent { unApplePayValidateMerchantEvent :: JSVal }
instance PToJSVal ApplePayValidateMerchantEvent where
pToJSVal = unApplePayValidateMerchantEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplePayValidateMerchantEvent where
pFromJSVal = ApplePayValidateMerchantEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplePayValidateMerchantEvent where
toJSVal = return . unApplePayValidateMerchantEvent
{-# INLINE toJSVal #-}
instance FromJSVal ApplePayValidateMerchantEvent where
fromJSVal v = fmap ApplePayValidateMerchantEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplePayValidateMerchantEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplePayValidateMerchantEvent where
makeObject = makeObject . unApplePayValidateMerchantEvent
instance IsEvent ApplePayValidateMerchantEvent
instance IsGObject ApplePayValidateMerchantEvent where
typeGType _ = gTypeApplePayValidateMerchantEvent
{-# INLINE typeGType #-}
noApplePayValidateMerchantEvent :: Maybe ApplePayValidateMerchantEvent
noApplePayValidateMerchantEvent = Nothing
{-# INLINE noApplePayValidateMerchantEvent #-}
gTypeApplePayValidateMerchantEvent :: JSM GType
gTypeApplePayValidateMerchantEvent = GType . Object <$> jsg "ApplePayValidateMerchantEvent"
newtype ApplicationCache = ApplicationCache { unApplicationCache :: JSVal }
instance PToJSVal ApplicationCache where
pToJSVal = unApplicationCache
{-# INLINE pToJSVal #-}
instance PFromJSVal ApplicationCache where
pFromJSVal = ApplicationCache
{-# INLINE pFromJSVal #-}
instance ToJSVal ApplicationCache where
toJSVal = return . unApplicationCache
{-# INLINE toJSVal #-}
instance FromJSVal ApplicationCache where
fromJSVal v = fmap ApplicationCache <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ApplicationCache
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ApplicationCache where
makeObject = makeObject . unApplicationCache
instance IsEventTarget ApplicationCache
instance IsGObject ApplicationCache where
typeGType _ = gTypeApplicationCache
{-# INLINE typeGType #-}
noApplicationCache :: Maybe ApplicationCache
noApplicationCache = Nothing
{-# INLINE noApplicationCache #-}
gTypeApplicationCache :: JSM GType
gTypeApplicationCache = GType . Object <$> jsg "ApplicationCache"
newtype AssignedNodesOptions = AssignedNodesOptions { unAssignedNodesOptions :: JSVal }
instance PToJSVal AssignedNodesOptions where
pToJSVal = unAssignedNodesOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal AssignedNodesOptions where
pFromJSVal = AssignedNodesOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal AssignedNodesOptions where
toJSVal = return . unAssignedNodesOptions
{-# INLINE toJSVal #-}
instance FromJSVal AssignedNodesOptions where
fromJSVal v = fmap AssignedNodesOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AssignedNodesOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AssignedNodesOptions where
makeObject = makeObject . unAssignedNodesOptions
instance IsGObject AssignedNodesOptions where
typeGType _ = gTypeAssignedNodesOptions
{-# INLINE typeGType #-}
noAssignedNodesOptions :: Maybe AssignedNodesOptions
noAssignedNodesOptions = Nothing
{-# INLINE noAssignedNodesOptions #-}
gTypeAssignedNodesOptions :: JSM GType
gTypeAssignedNodesOptions = GType . Object <$> jsg "AssignedNodesOptions"
newtype Attr = Attr { unAttr :: JSVal }
instance PToJSVal Attr where
pToJSVal = unAttr
{-# INLINE pToJSVal #-}
instance PFromJSVal Attr where
pFromJSVal = Attr
{-# INLINE pFromJSVal #-}
instance ToJSVal Attr where
toJSVal = return . unAttr
{-# INLINE toJSVal #-}
instance FromJSVal Attr where
fromJSVal v = fmap Attr <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Attr
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Attr where
makeObject = makeObject . unAttr
instance IsNode Attr
instance IsEventTarget Attr
instance IsGObject Attr where
typeGType _ = gTypeAttr
{-# INLINE typeGType #-}
noAttr :: Maybe Attr
noAttr = Nothing
{-# INLINE noAttr #-}
gTypeAttr :: JSM GType
gTypeAttr = GType . Object <$> jsg "Attr"
newtype AudioBuffer = AudioBuffer { unAudioBuffer :: JSVal }
instance PToJSVal AudioBuffer where
pToJSVal = unAudioBuffer
{-# INLINE pToJSVal #-}
instance PFromJSVal AudioBuffer where
pFromJSVal = AudioBuffer
{-# INLINE pFromJSVal #-}
instance ToJSVal AudioBuffer where
toJSVal = return . unAudioBuffer
{-# INLINE toJSVal #-}
instance FromJSVal AudioBuffer where
fromJSVal v = fmap AudioBuffer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AudioBuffer
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AudioBuffer where
makeObject = makeObject . unAudioBuffer
instance IsGObject AudioBuffer where
typeGType _ = gTypeAudioBuffer
{-# INLINE typeGType #-}
noAudioBuffer :: Maybe AudioBuffer
noAudioBuffer = Nothing
{-# INLINE noAudioBuffer #-}
gTypeAudioBuffer :: JSM GType
gTypeAudioBuffer = GType . Object <$> jsg "AudioBuffer"
newtype AudioBufferSourceNode = AudioBufferSourceNode { unAudioBufferSourceNode :: JSVal }
instance PToJSVal AudioBufferSourceNode where
pToJSVal = unAudioBufferSourceNode
{-# INLINE pToJSVal #-}
instance PFromJSVal AudioBufferSourceNode where
pFromJSVal = AudioBufferSourceNode
{-# INLINE pFromJSVal #-}
instance ToJSVal AudioBufferSourceNode where
toJSVal = return . unAudioBufferSourceNode
{-# INLINE toJSVal #-}
instance FromJSVal AudioBufferSourceNode where
fromJSVal v = fmap AudioBufferSourceNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AudioBufferSourceNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AudioBufferSourceNode where
makeObject = makeObject . unAudioBufferSourceNode
instance IsAudioNode AudioBufferSourceNode
instance IsEventTarget AudioBufferSourceNode
instance IsGObject AudioBufferSourceNode where
typeGType _ = gTypeAudioBufferSourceNode
{-# INLINE typeGType #-}
noAudioBufferSourceNode :: Maybe AudioBufferSourceNode
noAudioBufferSourceNode = Nothing
{-# INLINE noAudioBufferSourceNode #-}
gTypeAudioBufferSourceNode :: JSM GType
gTypeAudioBufferSourceNode = GType . Object <$> jsg "AudioBufferSourceNode"
newtype AudioContext = AudioContext { unAudioContext :: JSVal }
instance PToJSVal AudioContext where
pToJSVal = unAudioContext
{-# INLINE pToJSVal #-}
instance PFromJSVal AudioContext where
pFromJSVal = AudioContext
{-# INLINE pFromJSVal #-}
instance ToJSVal AudioContext where
toJSVal = return . unAudioContext
{-# INLINE toJSVal #-}
instance FromJSVal AudioContext where
fromJSVal v = fmap AudioContext <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AudioContext
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AudioContext where
makeObject = makeObject . unAudioContext
class (IsEventTarget o, IsGObject o) => IsAudioContext o
toAudioContext :: IsAudioContext o => o -> AudioContext
toAudioContext = AudioContext . coerce
instance IsAudioContext AudioContext
instance IsEventTarget AudioContext
instance IsGObject AudioContext where
typeGType _ = gTypeAudioContext
{-# INLINE typeGType #-}
noAudioContext :: Maybe AudioContext
noAudioContext = Nothing
{-# INLINE noAudioContext #-}
gTypeAudioContext :: JSM GType
gTypeAudioContext = GType . Object <$> jsg "AudioContext"
newtype AudioDestinationNode = AudioDestinationNode { unAudioDestinationNode :: JSVal }
instance PToJSVal AudioDestinationNode where
pToJSVal = unAudioDestinationNode
{-# INLINE pToJSVal #-}
instance PFromJSVal AudioDestinationNode where
pFromJSVal = AudioDestinationNode
{-# INLINE pFromJSVal #-}
instance ToJSVal AudioDestinationNode where
toJSVal = return . unAudioDestinationNode
{-# INLINE toJSVal #-}
instance FromJSVal AudioDestinationNode where
fromJSVal v = fmap AudioDestinationNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AudioDestinationNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AudioDestinationNode where
makeObject = makeObject . unAudioDestinationNode
instance IsAudioNode AudioDestinationNode
instance IsEventTarget AudioDestinationNode
instance IsGObject AudioDestinationNode where
typeGType _ = gTypeAudioDestinationNode
{-# INLINE typeGType #-}
noAudioDestinationNode :: Maybe AudioDestinationNode
noAudioDestinationNode = Nothing
{-# INLINE noAudioDestinationNode #-}
gTypeAudioDestinationNode :: JSM GType
gTypeAudioDestinationNode = GType . Object <$> jsg "AudioDestinationNode"
newtype AudioListener = AudioListener { unAudioListener :: JSVal }
instance PToJSVal AudioListener where
pToJSVal = unAudioListener
{-# INLINE pToJSVal #-}
instance PFromJSVal AudioListener where
pFromJSVal = AudioListener
{-# INLINE pFromJSVal #-}
instance ToJSVal AudioListener where
toJSVal = return . unAudioListener
{-# INLINE toJSVal #-}
instance FromJSVal AudioListener where
fromJSVal v = fmap AudioListener <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AudioListener
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AudioListener where
makeObject = makeObject . unAudioListener
instance IsGObject AudioListener where
typeGType _ = gTypeAudioListener
{-# INLINE typeGType #-}
noAudioListener :: Maybe AudioListener
noAudioListener = Nothing
{-# INLINE noAudioListener #-}
gTypeAudioListener :: JSM GType
gTypeAudioListener = GType . Object <$> jsg "AudioListener"
newtype AudioNode = AudioNode { unAudioNode :: JSVal }
instance PToJSVal AudioNode where
pToJSVal = unAudioNode
{-# INLINE pToJSVal #-}
instance PFromJSVal AudioNode where
pFromJSVal = AudioNode
{-# INLINE pFromJSVal #-}
instance ToJSVal AudioNode where
toJSVal = return . unAudioNode
{-# INLINE toJSVal #-}
instance FromJSVal AudioNode where
fromJSVal v = fmap AudioNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AudioNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AudioNode where
makeObject = makeObject . unAudioNode
class (IsEventTarget o, IsGObject o) => IsAudioNode o
toAudioNode :: IsAudioNode o => o -> AudioNode
toAudioNode = AudioNode . coerce
instance IsAudioNode AudioNode
instance IsEventTarget AudioNode
instance IsGObject AudioNode where
typeGType _ = gTypeAudioNode
{-# INLINE typeGType #-}
noAudioNode :: Maybe AudioNode
noAudioNode = Nothing
{-# INLINE noAudioNode #-}
gTypeAudioNode :: JSM GType
gTypeAudioNode = GType . Object <$> jsg "AudioNode"
newtype AudioParam = AudioParam { unAudioParam :: JSVal }
instance PToJSVal AudioParam where
pToJSVal = unAudioParam
{-# INLINE pToJSVal #-}
instance PFromJSVal AudioParam where
pFromJSVal = AudioParam
{-# INLINE pFromJSVal #-}
instance ToJSVal AudioParam where
toJSVal = return . unAudioParam
{-# INLINE toJSVal #-}
instance FromJSVal AudioParam where
fromJSVal v = fmap AudioParam <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AudioParam
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AudioParam where
makeObject = makeObject . unAudioParam
instance IsGObject AudioParam where
typeGType _ = gTypeAudioParam
{-# INLINE typeGType #-}
noAudioParam :: Maybe AudioParam
noAudioParam = Nothing
{-# INLINE noAudioParam #-}
gTypeAudioParam :: JSM GType
gTypeAudioParam = GType . Object <$> jsg "AudioParam"
newtype AudioProcessingEvent = AudioProcessingEvent { unAudioProcessingEvent :: JSVal }
instance PToJSVal AudioProcessingEvent where
pToJSVal = unAudioProcessingEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal AudioProcessingEvent where
pFromJSVal = AudioProcessingEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal AudioProcessingEvent where
toJSVal = return . unAudioProcessingEvent
{-# INLINE toJSVal #-}
instance FromJSVal AudioProcessingEvent where
fromJSVal v = fmap AudioProcessingEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AudioProcessingEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AudioProcessingEvent where
makeObject = makeObject . unAudioProcessingEvent
instance IsEvent AudioProcessingEvent
instance IsGObject AudioProcessingEvent where
typeGType _ = gTypeAudioProcessingEvent
{-# INLINE typeGType #-}
noAudioProcessingEvent :: Maybe AudioProcessingEvent
noAudioProcessingEvent = Nothing
{-# INLINE noAudioProcessingEvent #-}
gTypeAudioProcessingEvent :: JSM GType
gTypeAudioProcessingEvent = GType . Object <$> jsg "AudioProcessingEvent"
newtype AudioTrack = AudioTrack { unAudioTrack :: JSVal }
instance PToJSVal AudioTrack where
pToJSVal = unAudioTrack
{-# INLINE pToJSVal #-}
instance PFromJSVal AudioTrack where
pFromJSVal = AudioTrack
{-# INLINE pFromJSVal #-}
instance ToJSVal AudioTrack where
toJSVal = return . unAudioTrack
{-# INLINE toJSVal #-}
instance FromJSVal AudioTrack where
fromJSVal v = fmap AudioTrack <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AudioTrack
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AudioTrack where
makeObject = makeObject . unAudioTrack
instance IsGObject AudioTrack where
typeGType _ = gTypeAudioTrack
{-# INLINE typeGType #-}
noAudioTrack :: Maybe AudioTrack
noAudioTrack = Nothing
{-# INLINE noAudioTrack #-}
gTypeAudioTrack :: JSM GType
gTypeAudioTrack = GType . Object <$> jsg "AudioTrack"
newtype AudioTrackList = AudioTrackList { unAudioTrackList :: JSVal }
instance PToJSVal AudioTrackList where
pToJSVal = unAudioTrackList
{-# INLINE pToJSVal #-}
instance PFromJSVal AudioTrackList where
pFromJSVal = AudioTrackList
{-# INLINE pFromJSVal #-}
instance ToJSVal AudioTrackList where
toJSVal = return . unAudioTrackList
{-# INLINE toJSVal #-}
instance FromJSVal AudioTrackList where
fromJSVal v = fmap AudioTrackList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AudioTrackList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AudioTrackList where
makeObject = makeObject . unAudioTrackList
instance IsEventTarget AudioTrackList
instance IsGObject AudioTrackList where
typeGType _ = gTypeAudioTrackList
{-# INLINE typeGType #-}
noAudioTrackList :: Maybe AudioTrackList
noAudioTrackList = Nothing
{-# INLINE noAudioTrackList #-}
gTypeAudioTrackList :: JSM GType
gTypeAudioTrackList = GType . Object <$> jsg "AudioTrackList"
newtype AutocompleteErrorEvent = AutocompleteErrorEvent { unAutocompleteErrorEvent :: JSVal }
instance PToJSVal AutocompleteErrorEvent where
pToJSVal = unAutocompleteErrorEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal AutocompleteErrorEvent where
pFromJSVal = AutocompleteErrorEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal AutocompleteErrorEvent where
toJSVal = return . unAutocompleteErrorEvent
{-# INLINE toJSVal #-}
instance FromJSVal AutocompleteErrorEvent where
fromJSVal v = fmap AutocompleteErrorEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AutocompleteErrorEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AutocompleteErrorEvent where
makeObject = makeObject . unAutocompleteErrorEvent
instance IsEvent AutocompleteErrorEvent
instance IsGObject AutocompleteErrorEvent where
typeGType _ = gTypeAutocompleteErrorEvent
{-# INLINE typeGType #-}
noAutocompleteErrorEvent :: Maybe AutocompleteErrorEvent
noAutocompleteErrorEvent = Nothing
{-# INLINE noAutocompleteErrorEvent #-}
gTypeAutocompleteErrorEvent :: JSM GType
gTypeAutocompleteErrorEvent = GType . Object <$> jsg "AutocompleteErrorEvent"
newtype AutocompleteErrorEventInit = AutocompleteErrorEventInit { unAutocompleteErrorEventInit :: JSVal }
instance PToJSVal AutocompleteErrorEventInit where
pToJSVal = unAutocompleteErrorEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal AutocompleteErrorEventInit where
pFromJSVal = AutocompleteErrorEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal AutocompleteErrorEventInit where
toJSVal = return . unAutocompleteErrorEventInit
{-# INLINE toJSVal #-}
instance FromJSVal AutocompleteErrorEventInit where
fromJSVal v = fmap AutocompleteErrorEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . AutocompleteErrorEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject AutocompleteErrorEventInit where
makeObject = makeObject . unAutocompleteErrorEventInit
instance IsEventInit AutocompleteErrorEventInit
instance IsGObject AutocompleteErrorEventInit where
typeGType _ = gTypeAutocompleteErrorEventInit
{-# INLINE typeGType #-}
noAutocompleteErrorEventInit :: Maybe AutocompleteErrorEventInit
noAutocompleteErrorEventInit = Nothing
{-# INLINE noAutocompleteErrorEventInit #-}
gTypeAutocompleteErrorEventInit :: JSM GType
gTypeAutocompleteErrorEventInit = GType . Object <$> jsg "AutocompleteErrorEventInit"
newtype BarProp = BarProp { unBarProp :: JSVal }
instance PToJSVal BarProp where
pToJSVal = unBarProp
{-# INLINE pToJSVal #-}
instance PFromJSVal BarProp where
pFromJSVal = BarProp
{-# INLINE pFromJSVal #-}
instance ToJSVal BarProp where
toJSVal = return . unBarProp
{-# INLINE toJSVal #-}
instance FromJSVal BarProp where
fromJSVal v = fmap BarProp <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BarProp
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BarProp where
makeObject = makeObject . unBarProp
instance IsGObject BarProp where
typeGType _ = gTypeBarProp
{-# INLINE typeGType #-}
noBarProp :: Maybe BarProp
noBarProp = Nothing
{-# INLINE noBarProp #-}
gTypeBarProp :: JSM GType
gTypeBarProp = GType . Object <$> jsg "BarProp"
newtype BasicCredential = BasicCredential { unBasicCredential :: JSVal }
instance PToJSVal BasicCredential where
pToJSVal = unBasicCredential
{-# INLINE pToJSVal #-}
instance PFromJSVal BasicCredential where
pFromJSVal = BasicCredential
{-# INLINE pFromJSVal #-}
instance ToJSVal BasicCredential where
toJSVal = return . unBasicCredential
{-# INLINE toJSVal #-}
instance FromJSVal BasicCredential where
fromJSVal v = fmap BasicCredential <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BasicCredential
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BasicCredential where
makeObject = makeObject . unBasicCredential
class (IsGObject o) => IsBasicCredential o
toBasicCredential :: IsBasicCredential o => o -> BasicCredential
toBasicCredential = BasicCredential . coerce
instance IsBasicCredential BasicCredential
instance IsGObject BasicCredential where
typeGType _ = gTypeBasicCredential
{-# INLINE typeGType #-}
noBasicCredential :: Maybe BasicCredential
noBasicCredential = Nothing
{-# INLINE noBasicCredential #-}
gTypeBasicCredential :: JSM GType
gTypeBasicCredential = GType . Object <$> jsg "BasicCredential"
newtype BeforeLoadEvent = BeforeLoadEvent { unBeforeLoadEvent :: JSVal }
instance PToJSVal BeforeLoadEvent where
pToJSVal = unBeforeLoadEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal BeforeLoadEvent where
pFromJSVal = BeforeLoadEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal BeforeLoadEvent where
toJSVal = return . unBeforeLoadEvent
{-# INLINE toJSVal #-}
instance FromJSVal BeforeLoadEvent where
fromJSVal v = fmap BeforeLoadEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BeforeLoadEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BeforeLoadEvent where
makeObject = makeObject . unBeforeLoadEvent
instance IsEvent BeforeLoadEvent
instance IsGObject BeforeLoadEvent where
typeGType _ = gTypeBeforeLoadEvent
{-# INLINE typeGType #-}
noBeforeLoadEvent :: Maybe BeforeLoadEvent
noBeforeLoadEvent = Nothing
{-# INLINE noBeforeLoadEvent #-}
gTypeBeforeLoadEvent :: JSM GType
gTypeBeforeLoadEvent = GType . Object <$> jsg "BeforeLoadEvent"
newtype BeforeLoadEventInit = BeforeLoadEventInit { unBeforeLoadEventInit :: JSVal }
instance PToJSVal BeforeLoadEventInit where
pToJSVal = unBeforeLoadEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal BeforeLoadEventInit where
pFromJSVal = BeforeLoadEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal BeforeLoadEventInit where
toJSVal = return . unBeforeLoadEventInit
{-# INLINE toJSVal #-}
instance FromJSVal BeforeLoadEventInit where
fromJSVal v = fmap BeforeLoadEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BeforeLoadEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BeforeLoadEventInit where
makeObject = makeObject . unBeforeLoadEventInit
instance IsEventInit BeforeLoadEventInit
instance IsGObject BeforeLoadEventInit where
typeGType _ = gTypeBeforeLoadEventInit
{-# INLINE typeGType #-}
noBeforeLoadEventInit :: Maybe BeforeLoadEventInit
noBeforeLoadEventInit = Nothing
{-# INLINE noBeforeLoadEventInit #-}
gTypeBeforeLoadEventInit :: JSM GType
gTypeBeforeLoadEventInit = GType . Object <$> jsg "BeforeLoadEventInit"
newtype BeforeUnloadEvent = BeforeUnloadEvent { unBeforeUnloadEvent :: JSVal }
instance PToJSVal BeforeUnloadEvent where
pToJSVal = unBeforeUnloadEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal BeforeUnloadEvent where
pFromJSVal = BeforeUnloadEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal BeforeUnloadEvent where
toJSVal = return . unBeforeUnloadEvent
{-# INLINE toJSVal #-}
instance FromJSVal BeforeUnloadEvent where
fromJSVal v = fmap BeforeUnloadEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BeforeUnloadEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BeforeUnloadEvent where
makeObject = makeObject . unBeforeUnloadEvent
instance IsEvent BeforeUnloadEvent
instance IsGObject BeforeUnloadEvent where
typeGType _ = gTypeBeforeUnloadEvent
{-# INLINE typeGType #-}
noBeforeUnloadEvent :: Maybe BeforeUnloadEvent
noBeforeUnloadEvent = Nothing
{-# INLINE noBeforeUnloadEvent #-}
gTypeBeforeUnloadEvent :: JSM GType
gTypeBeforeUnloadEvent = GType . Object <$> jsg "BeforeUnloadEvent"
newtype BiquadFilterNode = BiquadFilterNode { unBiquadFilterNode :: JSVal }
instance PToJSVal BiquadFilterNode where
pToJSVal = unBiquadFilterNode
{-# INLINE pToJSVal #-}
instance PFromJSVal BiquadFilterNode where
pFromJSVal = BiquadFilterNode
{-# INLINE pFromJSVal #-}
instance ToJSVal BiquadFilterNode where
toJSVal = return . unBiquadFilterNode
{-# INLINE toJSVal #-}
instance FromJSVal BiquadFilterNode where
fromJSVal v = fmap BiquadFilterNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BiquadFilterNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BiquadFilterNode where
makeObject = makeObject . unBiquadFilterNode
instance IsAudioNode BiquadFilterNode
instance IsEventTarget BiquadFilterNode
instance IsGObject BiquadFilterNode where
typeGType _ = gTypeBiquadFilterNode
{-# INLINE typeGType #-}
noBiquadFilterNode :: Maybe BiquadFilterNode
noBiquadFilterNode = Nothing
{-# INLINE noBiquadFilterNode #-}
gTypeBiquadFilterNode :: JSM GType
gTypeBiquadFilterNode = GType . Object <$> jsg "BiquadFilterNode"
newtype Blob = Blob { unBlob :: JSVal }
instance PToJSVal Blob where
pToJSVal = unBlob
{-# INLINE pToJSVal #-}
instance PFromJSVal Blob where
pFromJSVal = Blob
{-# INLINE pFromJSVal #-}
instance ToJSVal Blob where
toJSVal = return . unBlob
{-# INLINE toJSVal #-}
instance FromJSVal Blob where
fromJSVal v = fmap Blob <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Blob
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Blob where
makeObject = makeObject . unBlob
class (IsGObject o) => IsBlob o
toBlob :: IsBlob o => o -> Blob
toBlob = Blob . coerce
instance IsBlob Blob
instance IsGObject Blob where
typeGType _ = gTypeBlob
{-# INLINE typeGType #-}
noBlob :: Maybe Blob
noBlob = Nothing
{-# INLINE noBlob #-}
gTypeBlob :: JSM GType
gTypeBlob = GType . Object <$> jsg "Blob"
newtype BlobPropertyBag = BlobPropertyBag { unBlobPropertyBag :: JSVal }
instance PToJSVal BlobPropertyBag where
pToJSVal = unBlobPropertyBag
{-# INLINE pToJSVal #-}
instance PFromJSVal BlobPropertyBag where
pFromJSVal = BlobPropertyBag
{-# INLINE pFromJSVal #-}
instance ToJSVal BlobPropertyBag where
toJSVal = return . unBlobPropertyBag
{-# INLINE toJSVal #-}
instance FromJSVal BlobPropertyBag where
fromJSVal v = fmap BlobPropertyBag <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . BlobPropertyBag
{-# INLINE fromJSValUnchecked #-}
instance MakeObject BlobPropertyBag where
makeObject = makeObject . unBlobPropertyBag
class (IsGObject o) => IsBlobPropertyBag o
toBlobPropertyBag :: IsBlobPropertyBag o => o -> BlobPropertyBag
toBlobPropertyBag = BlobPropertyBag . coerce
instance IsBlobPropertyBag BlobPropertyBag
instance IsGObject BlobPropertyBag where
typeGType _ = gTypeBlobPropertyBag
{-# INLINE typeGType #-}
noBlobPropertyBag :: Maybe BlobPropertyBag
noBlobPropertyBag = Nothing
{-# INLINE noBlobPropertyBag #-}
gTypeBlobPropertyBag :: JSM GType
gTypeBlobPropertyBag = GType . Object <$> jsg "BlobPropertyBag"
newtype Body = Body { unBody :: JSVal }
instance PToJSVal Body where
pToJSVal = unBody
{-# INLINE pToJSVal #-}
instance PFromJSVal Body where
pFromJSVal = Body
{-# INLINE pFromJSVal #-}
instance ToJSVal Body where
toJSVal = return . unBody
{-# INLINE toJSVal #-}
instance FromJSVal Body where
fromJSVal v = fmap Body <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Body
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Body where
makeObject = makeObject . unBody
class (IsGObject o) => IsBody o
toBody :: IsBody o => o -> Body
toBody = Body . coerce
instance IsBody Body
instance IsGObject Body where
typeGType _ = gTypeBody
{-# INLINE typeGType #-}
noBody :: Maybe Body
noBody = Nothing
{-# INLINE noBody #-}
gTypeBody :: JSM GType
gTypeBody = GType . Object <$> jsg "Body"
newtype ByteLengthQueuingStrategy = ByteLengthQueuingStrategy { unByteLengthQueuingStrategy :: JSVal }
instance PToJSVal ByteLengthQueuingStrategy where
pToJSVal = unByteLengthQueuingStrategy
{-# INLINE pToJSVal #-}
instance PFromJSVal ByteLengthQueuingStrategy where
pFromJSVal = ByteLengthQueuingStrategy
{-# INLINE pFromJSVal #-}
instance ToJSVal ByteLengthQueuingStrategy where
toJSVal = return . unByteLengthQueuingStrategy
{-# INLINE toJSVal #-}
instance FromJSVal ByteLengthQueuingStrategy where
fromJSVal v = fmap ByteLengthQueuingStrategy <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ByteLengthQueuingStrategy
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ByteLengthQueuingStrategy where
makeObject = makeObject . unByteLengthQueuingStrategy
instance IsGObject ByteLengthQueuingStrategy where
typeGType _ = gTypeByteLengthQueuingStrategy
{-# INLINE typeGType #-}
noByteLengthQueuingStrategy :: Maybe ByteLengthQueuingStrategy
noByteLengthQueuingStrategy = Nothing
{-# INLINE noByteLengthQueuingStrategy #-}
gTypeByteLengthQueuingStrategy :: JSM GType
gTypeByteLengthQueuingStrategy = GType . Object <$> jsg "ByteLengthQueuingStrategy"
newtype CDATASection = CDATASection { unCDATASection :: JSVal }
instance PToJSVal CDATASection where
pToJSVal = unCDATASection
{-# INLINE pToJSVal #-}
instance PFromJSVal CDATASection where
pFromJSVal = CDATASection
{-# INLINE pFromJSVal #-}
instance ToJSVal CDATASection where
toJSVal = return . unCDATASection
{-# INLINE toJSVal #-}
instance FromJSVal CDATASection where
fromJSVal v = fmap CDATASection <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CDATASection
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CDATASection where
makeObject = makeObject . unCDATASection
instance IsText CDATASection
instance IsCharacterData CDATASection
instance IsNode CDATASection
instance IsEventTarget CDATASection
instance IsNonDocumentTypeChildNode CDATASection
instance IsChildNode CDATASection
instance IsSlotable CDATASection
instance IsGObject CDATASection where
typeGType _ = gTypeCDATASection
{-# INLINE typeGType #-}
noCDATASection :: Maybe CDATASection
noCDATASection = Nothing
{-# INLINE noCDATASection #-}
gTypeCDATASection :: JSM GType
gTypeCDATASection = GType . Object <$> jsg "CDATASection"
newtype CSS = CSS { unCSS :: JSVal }
instance PToJSVal CSS where
pToJSVal = unCSS
{-# INLINE pToJSVal #-}
instance PFromJSVal CSS where
pFromJSVal = CSS
{-# INLINE pFromJSVal #-}
instance ToJSVal CSS where
toJSVal = return . unCSS
{-# INLINE toJSVal #-}
instance FromJSVal CSS where
fromJSVal v = fmap CSS <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSS
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSS where
makeObject = makeObject . unCSS
instance IsGObject CSS where
typeGType _ = gTypeCSS
{-# INLINE typeGType #-}
noCSS :: Maybe CSS
noCSS = Nothing
{-# INLINE noCSS #-}
gTypeCSS :: JSM GType
gTypeCSS = GType . Object <$> jsg "CSS"
newtype CSSFontFaceLoadEvent = CSSFontFaceLoadEvent { unCSSFontFaceLoadEvent :: JSVal }
instance PToJSVal CSSFontFaceLoadEvent where
pToJSVal = unCSSFontFaceLoadEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSFontFaceLoadEvent where
pFromJSVal = CSSFontFaceLoadEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSFontFaceLoadEvent where
toJSVal = return . unCSSFontFaceLoadEvent
{-# INLINE toJSVal #-}
instance FromJSVal CSSFontFaceLoadEvent where
fromJSVal v = fmap CSSFontFaceLoadEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSFontFaceLoadEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSFontFaceLoadEvent where
makeObject = makeObject . unCSSFontFaceLoadEvent
instance IsEvent CSSFontFaceLoadEvent
instance IsGObject CSSFontFaceLoadEvent where
typeGType _ = gTypeCSSFontFaceLoadEvent
{-# INLINE typeGType #-}
noCSSFontFaceLoadEvent :: Maybe CSSFontFaceLoadEvent
noCSSFontFaceLoadEvent = Nothing
{-# INLINE noCSSFontFaceLoadEvent #-}
gTypeCSSFontFaceLoadEvent :: JSM GType
gTypeCSSFontFaceLoadEvent = GType . Object <$> jsg "CSSFontFaceLoadEvent"
newtype CSSFontFaceLoadEventInit = CSSFontFaceLoadEventInit { unCSSFontFaceLoadEventInit :: JSVal }
instance PToJSVal CSSFontFaceLoadEventInit where
pToJSVal = unCSSFontFaceLoadEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSFontFaceLoadEventInit where
pFromJSVal = CSSFontFaceLoadEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSFontFaceLoadEventInit where
toJSVal = return . unCSSFontFaceLoadEventInit
{-# INLINE toJSVal #-}
instance FromJSVal CSSFontFaceLoadEventInit where
fromJSVal v = fmap CSSFontFaceLoadEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSFontFaceLoadEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSFontFaceLoadEventInit where
makeObject = makeObject . unCSSFontFaceLoadEventInit
instance IsEventInit CSSFontFaceLoadEventInit
instance IsGObject CSSFontFaceLoadEventInit where
typeGType _ = gTypeCSSFontFaceLoadEventInit
{-# INLINE typeGType #-}
noCSSFontFaceLoadEventInit :: Maybe CSSFontFaceLoadEventInit
noCSSFontFaceLoadEventInit = Nothing
{-# INLINE noCSSFontFaceLoadEventInit #-}
gTypeCSSFontFaceLoadEventInit :: JSM GType
gTypeCSSFontFaceLoadEventInit = GType . Object <$> jsg "CSSFontFaceLoadEventInit"
newtype CSSFontFaceRule = CSSFontFaceRule { unCSSFontFaceRule :: JSVal }
instance PToJSVal CSSFontFaceRule where
pToJSVal = unCSSFontFaceRule
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSFontFaceRule where
pFromJSVal = CSSFontFaceRule
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSFontFaceRule where
toJSVal = return . unCSSFontFaceRule
{-# INLINE toJSVal #-}
instance FromJSVal CSSFontFaceRule where
fromJSVal v = fmap CSSFontFaceRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSFontFaceRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSFontFaceRule where
makeObject = makeObject . unCSSFontFaceRule
instance IsCSSRule CSSFontFaceRule
instance IsGObject CSSFontFaceRule where
typeGType _ = gTypeCSSFontFaceRule
{-# INLINE typeGType #-}
noCSSFontFaceRule :: Maybe CSSFontFaceRule
noCSSFontFaceRule = Nothing
{-# INLINE noCSSFontFaceRule #-}
gTypeCSSFontFaceRule :: JSM GType
gTypeCSSFontFaceRule = GType . Object <$> jsg "CSSFontFaceRule"
newtype CSSImportRule = CSSImportRule { unCSSImportRule :: JSVal }
instance PToJSVal CSSImportRule where
pToJSVal = unCSSImportRule
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSImportRule where
pFromJSVal = CSSImportRule
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSImportRule where
toJSVal = return . unCSSImportRule
{-# INLINE toJSVal #-}
instance FromJSVal CSSImportRule where
fromJSVal v = fmap CSSImportRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSImportRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSImportRule where
makeObject = makeObject . unCSSImportRule
instance IsCSSRule CSSImportRule
instance IsGObject CSSImportRule where
typeGType _ = gTypeCSSImportRule
{-# INLINE typeGType #-}
noCSSImportRule :: Maybe CSSImportRule
noCSSImportRule = Nothing
{-# INLINE noCSSImportRule #-}
gTypeCSSImportRule :: JSM GType
gTypeCSSImportRule = GType . Object <$> jsg "CSSImportRule"
newtype CSSKeyframeRule = CSSKeyframeRule { unCSSKeyframeRule :: JSVal }
instance PToJSVal CSSKeyframeRule where
pToJSVal = unCSSKeyframeRule
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSKeyframeRule where
pFromJSVal = CSSKeyframeRule
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSKeyframeRule where
toJSVal = return . unCSSKeyframeRule
{-# INLINE toJSVal #-}
instance FromJSVal CSSKeyframeRule where
fromJSVal v = fmap CSSKeyframeRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSKeyframeRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSKeyframeRule where
makeObject = makeObject . unCSSKeyframeRule
instance IsCSSRule CSSKeyframeRule
instance IsGObject CSSKeyframeRule where
typeGType _ = gTypeCSSKeyframeRule
{-# INLINE typeGType #-}
noCSSKeyframeRule :: Maybe CSSKeyframeRule
noCSSKeyframeRule = Nothing
{-# INLINE noCSSKeyframeRule #-}
gTypeCSSKeyframeRule :: JSM GType
gTypeCSSKeyframeRule = GType . Object <$> jsg "CSSKeyframeRule"
newtype CSSKeyframesRule = CSSKeyframesRule { unCSSKeyframesRule :: JSVal }
instance PToJSVal CSSKeyframesRule where
pToJSVal = unCSSKeyframesRule
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSKeyframesRule where
pFromJSVal = CSSKeyframesRule
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSKeyframesRule where
toJSVal = return . unCSSKeyframesRule
{-# INLINE toJSVal #-}
instance FromJSVal CSSKeyframesRule where
fromJSVal v = fmap CSSKeyframesRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSKeyframesRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSKeyframesRule where
makeObject = makeObject . unCSSKeyframesRule
instance IsCSSRule CSSKeyframesRule
instance IsGObject CSSKeyframesRule where
typeGType _ = gTypeCSSKeyframesRule
{-# INLINE typeGType #-}
noCSSKeyframesRule :: Maybe CSSKeyframesRule
noCSSKeyframesRule = Nothing
{-# INLINE noCSSKeyframesRule #-}
gTypeCSSKeyframesRule :: JSM GType
gTypeCSSKeyframesRule = GType . Object <$> jsg "CSSKeyframesRule"
newtype CSSMediaRule = CSSMediaRule { unCSSMediaRule :: JSVal }
instance PToJSVal CSSMediaRule where
pToJSVal = unCSSMediaRule
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSMediaRule where
pFromJSVal = CSSMediaRule
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSMediaRule where
toJSVal = return . unCSSMediaRule
{-# INLINE toJSVal #-}
instance FromJSVal CSSMediaRule where
fromJSVal v = fmap CSSMediaRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSMediaRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSMediaRule where
makeObject = makeObject . unCSSMediaRule
instance IsCSSRule CSSMediaRule
instance IsGObject CSSMediaRule where
typeGType _ = gTypeCSSMediaRule
{-# INLINE typeGType #-}
noCSSMediaRule :: Maybe CSSMediaRule
noCSSMediaRule = Nothing
{-# INLINE noCSSMediaRule #-}
gTypeCSSMediaRule :: JSM GType
gTypeCSSMediaRule = GType . Object <$> jsg "CSSMediaRule"
newtype CSSNamespaceRule = CSSNamespaceRule { unCSSNamespaceRule :: JSVal }
instance PToJSVal CSSNamespaceRule where
pToJSVal = unCSSNamespaceRule
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSNamespaceRule where
pFromJSVal = CSSNamespaceRule
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSNamespaceRule where
toJSVal = return . unCSSNamespaceRule
{-# INLINE toJSVal #-}
instance FromJSVal CSSNamespaceRule where
fromJSVal v = fmap CSSNamespaceRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSNamespaceRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSNamespaceRule where
makeObject = makeObject . unCSSNamespaceRule
instance IsCSSRule CSSNamespaceRule
instance IsGObject CSSNamespaceRule where
typeGType _ = gTypeCSSNamespaceRule
{-# INLINE typeGType #-}
noCSSNamespaceRule :: Maybe CSSNamespaceRule
noCSSNamespaceRule = Nothing
{-# INLINE noCSSNamespaceRule #-}
gTypeCSSNamespaceRule :: JSM GType
gTypeCSSNamespaceRule = GType . Object <$> jsg "CSSNamespaceRule"
newtype CSSPageRule = CSSPageRule { unCSSPageRule :: JSVal }
instance PToJSVal CSSPageRule where
pToJSVal = unCSSPageRule
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSPageRule where
pFromJSVal = CSSPageRule
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSPageRule where
toJSVal = return . unCSSPageRule
{-# INLINE toJSVal #-}
instance FromJSVal CSSPageRule where
fromJSVal v = fmap CSSPageRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSPageRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSPageRule where
makeObject = makeObject . unCSSPageRule
instance IsCSSRule CSSPageRule
instance IsGObject CSSPageRule where
typeGType _ = gTypeCSSPageRule
{-# INLINE typeGType #-}
noCSSPageRule :: Maybe CSSPageRule
noCSSPageRule = Nothing
{-# INLINE noCSSPageRule #-}
gTypeCSSPageRule :: JSM GType
gTypeCSSPageRule = GType . Object <$> jsg "CSSPageRule"
newtype CSSPrimitiveValue = CSSPrimitiveValue { unCSSPrimitiveValue :: JSVal }
instance PToJSVal CSSPrimitiveValue where
pToJSVal = unCSSPrimitiveValue
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSPrimitiveValue where
pFromJSVal = CSSPrimitiveValue
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSPrimitiveValue where
toJSVal = return . unCSSPrimitiveValue
{-# INLINE toJSVal #-}
instance FromJSVal CSSPrimitiveValue where
fromJSVal v = fmap CSSPrimitiveValue <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSPrimitiveValue
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSPrimitiveValue where
makeObject = makeObject . unCSSPrimitiveValue
instance IsCSSValue CSSPrimitiveValue
instance IsGObject CSSPrimitiveValue where
typeGType _ = gTypeCSSPrimitiveValue
{-# INLINE typeGType #-}
noCSSPrimitiveValue :: Maybe CSSPrimitiveValue
noCSSPrimitiveValue = Nothing
{-# INLINE noCSSPrimitiveValue #-}
gTypeCSSPrimitiveValue :: JSM GType
gTypeCSSPrimitiveValue = GType . Object <$> jsg "CSSPrimitiveValue"
newtype CSSRule = CSSRule { unCSSRule :: JSVal }
instance PToJSVal CSSRule where
pToJSVal = unCSSRule
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSRule where
pFromJSVal = CSSRule
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSRule where
toJSVal = return . unCSSRule
{-# INLINE toJSVal #-}
instance FromJSVal CSSRule where
fromJSVal v = fmap CSSRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSRule where
makeObject = makeObject . unCSSRule
class (IsGObject o) => IsCSSRule o
toCSSRule :: IsCSSRule o => o -> CSSRule
toCSSRule = CSSRule . coerce
instance IsCSSRule CSSRule
instance IsGObject CSSRule where
typeGType _ = gTypeCSSRule
{-# INLINE typeGType #-}
noCSSRule :: Maybe CSSRule
noCSSRule = Nothing
{-# INLINE noCSSRule #-}
gTypeCSSRule :: JSM GType
gTypeCSSRule = GType . Object <$> jsg "CSSRule"
newtype CSSRuleList = CSSRuleList { unCSSRuleList :: JSVal }
instance PToJSVal CSSRuleList where
pToJSVal = unCSSRuleList
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSRuleList where
pFromJSVal = CSSRuleList
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSRuleList where
toJSVal = return . unCSSRuleList
{-# INLINE toJSVal #-}
instance FromJSVal CSSRuleList where
fromJSVal v = fmap CSSRuleList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSRuleList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSRuleList where
makeObject = makeObject . unCSSRuleList
instance IsGObject CSSRuleList where
typeGType _ = gTypeCSSRuleList
{-# INLINE typeGType #-}
noCSSRuleList :: Maybe CSSRuleList
noCSSRuleList = Nothing
{-# INLINE noCSSRuleList #-}
gTypeCSSRuleList :: JSM GType
gTypeCSSRuleList = GType . Object <$> jsg "CSSRuleList"
newtype CSSStyleDeclaration = CSSStyleDeclaration { unCSSStyleDeclaration :: JSVal }
instance PToJSVal CSSStyleDeclaration where
pToJSVal = unCSSStyleDeclaration
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSStyleDeclaration where
pFromJSVal = CSSStyleDeclaration
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSStyleDeclaration where
toJSVal = return . unCSSStyleDeclaration
{-# INLINE toJSVal #-}
instance FromJSVal CSSStyleDeclaration where
fromJSVal v = fmap CSSStyleDeclaration <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSStyleDeclaration
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSStyleDeclaration where
makeObject = makeObject . unCSSStyleDeclaration
instance IsGObject CSSStyleDeclaration where
typeGType _ = gTypeCSSStyleDeclaration
{-# INLINE typeGType #-}
noCSSStyleDeclaration :: Maybe CSSStyleDeclaration
noCSSStyleDeclaration = Nothing
{-# INLINE noCSSStyleDeclaration #-}
gTypeCSSStyleDeclaration :: JSM GType
gTypeCSSStyleDeclaration = GType . Object <$> jsg "CSSStyleDeclaration"
newtype CSSStyleRule = CSSStyleRule { unCSSStyleRule :: JSVal }
instance PToJSVal CSSStyleRule where
pToJSVal = unCSSStyleRule
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSStyleRule where
pFromJSVal = CSSStyleRule
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSStyleRule where
toJSVal = return . unCSSStyleRule
{-# INLINE toJSVal #-}
instance FromJSVal CSSStyleRule where
fromJSVal v = fmap CSSStyleRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSStyleRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSStyleRule where
makeObject = makeObject . unCSSStyleRule
instance IsCSSRule CSSStyleRule
instance IsGObject CSSStyleRule where
typeGType _ = gTypeCSSStyleRule
{-# INLINE typeGType #-}
noCSSStyleRule :: Maybe CSSStyleRule
noCSSStyleRule = Nothing
{-# INLINE noCSSStyleRule #-}
gTypeCSSStyleRule :: JSM GType
gTypeCSSStyleRule = GType . Object <$> jsg "CSSStyleRule"
newtype CSSStyleSheet = CSSStyleSheet { unCSSStyleSheet :: JSVal }
instance PToJSVal CSSStyleSheet where
pToJSVal = unCSSStyleSheet
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSStyleSheet where
pFromJSVal = CSSStyleSheet
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSStyleSheet where
toJSVal = return . unCSSStyleSheet
{-# INLINE toJSVal #-}
instance FromJSVal CSSStyleSheet where
fromJSVal v = fmap CSSStyleSheet <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSStyleSheet
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSStyleSheet where
makeObject = makeObject . unCSSStyleSheet
instance IsStyleSheet CSSStyleSheet
instance IsGObject CSSStyleSheet where
typeGType _ = gTypeCSSStyleSheet
{-# INLINE typeGType #-}
noCSSStyleSheet :: Maybe CSSStyleSheet
noCSSStyleSheet = Nothing
{-# INLINE noCSSStyleSheet #-}
gTypeCSSStyleSheet :: JSM GType
gTypeCSSStyleSheet = GType . Object <$> jsg "CSSStyleSheet"
newtype CSSSupportsRule = CSSSupportsRule { unCSSSupportsRule :: JSVal }
instance PToJSVal CSSSupportsRule where
pToJSVal = unCSSSupportsRule
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSSupportsRule where
pFromJSVal = CSSSupportsRule
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSSupportsRule where
toJSVal = return . unCSSSupportsRule
{-# INLINE toJSVal #-}
instance FromJSVal CSSSupportsRule where
fromJSVal v = fmap CSSSupportsRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSSupportsRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSSupportsRule where
makeObject = makeObject . unCSSSupportsRule
instance IsCSSRule CSSSupportsRule
instance IsGObject CSSSupportsRule where
typeGType _ = gTypeCSSSupportsRule
{-# INLINE typeGType #-}
noCSSSupportsRule :: Maybe CSSSupportsRule
noCSSSupportsRule = Nothing
{-# INLINE noCSSSupportsRule #-}
gTypeCSSSupportsRule :: JSM GType
gTypeCSSSupportsRule = GType . Object <$> jsg "CSSSupportsRule"
newtype CSSUnknownRule = CSSUnknownRule { unCSSUnknownRule :: JSVal }
instance PToJSVal CSSUnknownRule where
pToJSVal = unCSSUnknownRule
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSUnknownRule where
pFromJSVal = CSSUnknownRule
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSUnknownRule where
toJSVal = return . unCSSUnknownRule
{-# INLINE toJSVal #-}
instance FromJSVal CSSUnknownRule where
fromJSVal v = fmap CSSUnknownRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSUnknownRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSUnknownRule where
makeObject = makeObject . unCSSUnknownRule
instance IsCSSRule CSSUnknownRule
instance IsGObject CSSUnknownRule where
typeGType _ = gTypeCSSUnknownRule
{-# INLINE typeGType #-}
noCSSUnknownRule :: Maybe CSSUnknownRule
noCSSUnknownRule = Nothing
{-# INLINE noCSSUnknownRule #-}
gTypeCSSUnknownRule :: JSM GType
gTypeCSSUnknownRule = GType . Object <$> jsg "CSSUnknownRule"
newtype CSSValue = CSSValue { unCSSValue :: JSVal }
instance PToJSVal CSSValue where
pToJSVal = unCSSValue
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSValue where
pFromJSVal = CSSValue
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSValue where
toJSVal = return . unCSSValue
{-# INLINE toJSVal #-}
instance FromJSVal CSSValue where
fromJSVal v = fmap CSSValue <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSValue
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSValue where
makeObject = makeObject . unCSSValue
class (IsGObject o) => IsCSSValue o
toCSSValue :: IsCSSValue o => o -> CSSValue
toCSSValue = CSSValue . coerce
instance IsCSSValue CSSValue
instance IsGObject CSSValue where
typeGType _ = gTypeCSSValue
{-# INLINE typeGType #-}
noCSSValue :: Maybe CSSValue
noCSSValue = Nothing
{-# INLINE noCSSValue #-}
gTypeCSSValue :: JSM GType
gTypeCSSValue = GType . Object <$> jsg "CSSValue"
newtype CSSValueList = CSSValueList { unCSSValueList :: JSVal }
instance PToJSVal CSSValueList where
pToJSVal = unCSSValueList
{-# INLINE pToJSVal #-}
instance PFromJSVal CSSValueList where
pFromJSVal = CSSValueList
{-# INLINE pFromJSVal #-}
instance ToJSVal CSSValueList where
toJSVal = return . unCSSValueList
{-# INLINE toJSVal #-}
instance FromJSVal CSSValueList where
fromJSVal v = fmap CSSValueList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CSSValueList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CSSValueList where
makeObject = makeObject . unCSSValueList
instance IsCSSValue CSSValueList
instance IsGObject CSSValueList where
typeGType _ = gTypeCSSValueList
{-# INLINE typeGType #-}
noCSSValueList :: Maybe CSSValueList
noCSSValueList = Nothing
{-# INLINE noCSSValueList #-}
gTypeCSSValueList :: JSM GType
gTypeCSSValueList = GType . Object <$> jsg "CSSValueList"
newtype CanvasCaptureMediaStreamTrack = CanvasCaptureMediaStreamTrack { unCanvasCaptureMediaStreamTrack :: JSVal }
instance PToJSVal CanvasCaptureMediaStreamTrack where
pToJSVal = unCanvasCaptureMediaStreamTrack
{-# INLINE pToJSVal #-}
instance PFromJSVal CanvasCaptureMediaStreamTrack where
pFromJSVal = CanvasCaptureMediaStreamTrack
{-# INLINE pFromJSVal #-}
instance ToJSVal CanvasCaptureMediaStreamTrack where
toJSVal = return . unCanvasCaptureMediaStreamTrack
{-# INLINE toJSVal #-}
instance FromJSVal CanvasCaptureMediaStreamTrack where
fromJSVal v = fmap CanvasCaptureMediaStreamTrack <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CanvasCaptureMediaStreamTrack
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CanvasCaptureMediaStreamTrack where
makeObject = makeObject . unCanvasCaptureMediaStreamTrack
instance IsMediaStreamTrack CanvasCaptureMediaStreamTrack
instance IsEventTarget CanvasCaptureMediaStreamTrack
instance IsGObject CanvasCaptureMediaStreamTrack where
typeGType _ = gTypeCanvasCaptureMediaStreamTrack
{-# INLINE typeGType #-}
noCanvasCaptureMediaStreamTrack :: Maybe CanvasCaptureMediaStreamTrack
noCanvasCaptureMediaStreamTrack = Nothing
{-# INLINE noCanvasCaptureMediaStreamTrack #-}
gTypeCanvasCaptureMediaStreamTrack :: JSM GType
gTypeCanvasCaptureMediaStreamTrack = GType . Object <$> jsg "CanvasCaptureMediaStreamTrack"
newtype CanvasGradient = CanvasGradient { unCanvasGradient :: JSVal }
instance PToJSVal CanvasGradient where
pToJSVal = unCanvasGradient
{-# INLINE pToJSVal #-}
instance PFromJSVal CanvasGradient where
pFromJSVal = CanvasGradient
{-# INLINE pFromJSVal #-}
instance ToJSVal CanvasGradient where
toJSVal = return . unCanvasGradient
{-# INLINE toJSVal #-}
instance FromJSVal CanvasGradient where
fromJSVal v = fmap CanvasGradient <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CanvasGradient
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CanvasGradient where
makeObject = makeObject . unCanvasGradient
instance IsGObject CanvasGradient where
typeGType _ = gTypeCanvasGradient
{-# INLINE typeGType #-}
noCanvasGradient :: Maybe CanvasGradient
noCanvasGradient = Nothing
{-# INLINE noCanvasGradient #-}
gTypeCanvasGradient :: JSM GType
gTypeCanvasGradient = GType . Object <$> jsg "CanvasGradient"
newtype CanvasPath = CanvasPath { unCanvasPath :: JSVal }
instance PToJSVal CanvasPath where
pToJSVal = unCanvasPath
{-# INLINE pToJSVal #-}
instance PFromJSVal CanvasPath where
pFromJSVal = CanvasPath
{-# INLINE pFromJSVal #-}
instance ToJSVal CanvasPath where
toJSVal = return . unCanvasPath
{-# INLINE toJSVal #-}
instance FromJSVal CanvasPath where
fromJSVal v = fmap CanvasPath <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CanvasPath
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CanvasPath where
makeObject = makeObject . unCanvasPath
class (IsGObject o) => IsCanvasPath o
toCanvasPath :: IsCanvasPath o => o -> CanvasPath
toCanvasPath = CanvasPath . coerce
instance IsCanvasPath CanvasPath
instance IsGObject CanvasPath where
typeGType _ = gTypeCanvasPath
{-# INLINE typeGType #-}
noCanvasPath :: Maybe CanvasPath
noCanvasPath = Nothing
{-# INLINE noCanvasPath #-}
gTypeCanvasPath :: JSM GType
gTypeCanvasPath = GType . Object <$> jsg "CanvasPath"
newtype CanvasPattern = CanvasPattern { unCanvasPattern :: JSVal }
instance PToJSVal CanvasPattern where
pToJSVal = unCanvasPattern
{-# INLINE pToJSVal #-}
instance PFromJSVal CanvasPattern where
pFromJSVal = CanvasPattern
{-# INLINE pFromJSVal #-}
instance ToJSVal CanvasPattern where
toJSVal = return . unCanvasPattern
{-# INLINE toJSVal #-}
instance FromJSVal CanvasPattern where
fromJSVal v = fmap CanvasPattern <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CanvasPattern
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CanvasPattern where
makeObject = makeObject . unCanvasPattern
instance IsGObject CanvasPattern where
typeGType _ = gTypeCanvasPattern
{-# INLINE typeGType #-}
noCanvasPattern :: Maybe CanvasPattern
noCanvasPattern = Nothing
{-# INLINE noCanvasPattern #-}
gTypeCanvasPattern :: JSM GType
gTypeCanvasPattern = GType . Object <$> jsg "CanvasPattern"
newtype CanvasProxy = CanvasProxy { unCanvasProxy :: JSVal }
instance PToJSVal CanvasProxy where
pToJSVal = unCanvasProxy
{-# INLINE pToJSVal #-}
instance PFromJSVal CanvasProxy where
pFromJSVal = CanvasProxy
{-# INLINE pFromJSVal #-}
instance ToJSVal CanvasProxy where
toJSVal = return . unCanvasProxy
{-# INLINE toJSVal #-}
instance FromJSVal CanvasProxy where
fromJSVal v = fmap CanvasProxy <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CanvasProxy
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CanvasProxy where
makeObject = makeObject . unCanvasProxy
instance IsGObject CanvasProxy where
typeGType _ = gTypeCanvasProxy
{-# INLINE typeGType #-}
noCanvasProxy :: Maybe CanvasProxy
noCanvasProxy = Nothing
{-# INLINE noCanvasProxy #-}
gTypeCanvasProxy :: JSM GType
gTypeCanvasProxy = GType . Object <$> jsg "CanvasProxy"
newtype CanvasRenderingContext2D = CanvasRenderingContext2D { unCanvasRenderingContext2D :: JSVal }
instance PToJSVal CanvasRenderingContext2D where
pToJSVal = unCanvasRenderingContext2D
{-# INLINE pToJSVal #-}
instance PFromJSVal CanvasRenderingContext2D where
pFromJSVal = CanvasRenderingContext2D
{-# INLINE pFromJSVal #-}
instance ToJSVal CanvasRenderingContext2D where
toJSVal = return . unCanvasRenderingContext2D
{-# INLINE toJSVal #-}
instance FromJSVal CanvasRenderingContext2D where
fromJSVal v = fmap CanvasRenderingContext2D <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CanvasRenderingContext2D
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CanvasRenderingContext2D where
makeObject = makeObject . unCanvasRenderingContext2D
instance IsCanvasPath CanvasRenderingContext2D
instance IsGObject CanvasRenderingContext2D where
typeGType _ = gTypeCanvasRenderingContext2D
{-# INLINE typeGType #-}
noCanvasRenderingContext2D :: Maybe CanvasRenderingContext2D
noCanvasRenderingContext2D = Nothing
{-# INLINE noCanvasRenderingContext2D #-}
gTypeCanvasRenderingContext2D :: JSM GType
gTypeCanvasRenderingContext2D = GType . Object <$> jsg "CanvasRenderingContext2D"
newtype ChannelMergerNode = ChannelMergerNode { unChannelMergerNode :: JSVal }
instance PToJSVal ChannelMergerNode where
pToJSVal = unChannelMergerNode
{-# INLINE pToJSVal #-}
instance PFromJSVal ChannelMergerNode where
pFromJSVal = ChannelMergerNode
{-# INLINE pFromJSVal #-}
instance ToJSVal ChannelMergerNode where
toJSVal = return . unChannelMergerNode
{-# INLINE toJSVal #-}
instance FromJSVal ChannelMergerNode where
fromJSVal v = fmap ChannelMergerNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ChannelMergerNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ChannelMergerNode where
makeObject = makeObject . unChannelMergerNode
instance IsAudioNode ChannelMergerNode
instance IsEventTarget ChannelMergerNode
instance IsGObject ChannelMergerNode where
typeGType _ = gTypeChannelMergerNode
{-# INLINE typeGType #-}
noChannelMergerNode :: Maybe ChannelMergerNode
noChannelMergerNode = Nothing
{-# INLINE noChannelMergerNode #-}
gTypeChannelMergerNode :: JSM GType
gTypeChannelMergerNode = GType . Object <$> jsg "ChannelMergerNode"
newtype ChannelSplitterNode = ChannelSplitterNode { unChannelSplitterNode :: JSVal }
instance PToJSVal ChannelSplitterNode where
pToJSVal = unChannelSplitterNode
{-# INLINE pToJSVal #-}
instance PFromJSVal ChannelSplitterNode where
pFromJSVal = ChannelSplitterNode
{-# INLINE pFromJSVal #-}
instance ToJSVal ChannelSplitterNode where
toJSVal = return . unChannelSplitterNode
{-# INLINE toJSVal #-}
instance FromJSVal ChannelSplitterNode where
fromJSVal v = fmap ChannelSplitterNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ChannelSplitterNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ChannelSplitterNode where
makeObject = makeObject . unChannelSplitterNode
instance IsAudioNode ChannelSplitterNode
instance IsEventTarget ChannelSplitterNode
instance IsGObject ChannelSplitterNode where
typeGType _ = gTypeChannelSplitterNode
{-# INLINE typeGType #-}
noChannelSplitterNode :: Maybe ChannelSplitterNode
noChannelSplitterNode = Nothing
{-# INLINE noChannelSplitterNode #-}
gTypeChannelSplitterNode :: JSM GType
gTypeChannelSplitterNode = GType . Object <$> jsg "ChannelSplitterNode"
newtype CharacterData = CharacterData { unCharacterData :: JSVal }
instance PToJSVal CharacterData where
pToJSVal = unCharacterData
{-# INLINE pToJSVal #-}
instance PFromJSVal CharacterData where
pFromJSVal = CharacterData
{-# INLINE pFromJSVal #-}
instance ToJSVal CharacterData where
toJSVal = return . unCharacterData
{-# INLINE toJSVal #-}
instance FromJSVal CharacterData where
fromJSVal v = fmap CharacterData <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CharacterData
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CharacterData where
makeObject = makeObject . unCharacterData
class (IsNode o, IsEventTarget o, IsNonDocumentTypeChildNode o, IsChildNode o, IsGObject o) => IsCharacterData o
toCharacterData :: IsCharacterData o => o -> CharacterData
toCharacterData = CharacterData . coerce
instance IsCharacterData CharacterData
instance IsNode CharacterData
instance IsEventTarget CharacterData
instance IsNonDocumentTypeChildNode CharacterData
instance IsChildNode CharacterData
instance IsGObject CharacterData where
typeGType _ = gTypeCharacterData
{-# INLINE typeGType #-}
noCharacterData :: Maybe CharacterData
noCharacterData = Nothing
{-# INLINE noCharacterData #-}
gTypeCharacterData :: JSM GType
gTypeCharacterData = GType . Object <$> jsg "CharacterData"
newtype ChildNode = ChildNode { unChildNode :: JSVal }
instance PToJSVal ChildNode where
pToJSVal = unChildNode
{-# INLINE pToJSVal #-}
instance PFromJSVal ChildNode where
pFromJSVal = ChildNode
{-# INLINE pFromJSVal #-}
instance ToJSVal ChildNode where
toJSVal = return . unChildNode
{-# INLINE toJSVal #-}
instance FromJSVal ChildNode where
fromJSVal v = fmap ChildNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ChildNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ChildNode where
makeObject = makeObject . unChildNode
class (IsGObject o) => IsChildNode o
toChildNode :: IsChildNode o => o -> ChildNode
toChildNode = ChildNode . coerce
instance IsChildNode ChildNode
instance IsGObject ChildNode where
typeGType _ = gTypeChildNode
{-# INLINE typeGType #-}
noChildNode :: Maybe ChildNode
noChildNode = Nothing
{-# INLINE noChildNode #-}
gTypeChildNode :: JSM GType
gTypeChildNode = GType . Object <$> jsg "ChildNode"
newtype ClipboardEvent = ClipboardEvent { unClipboardEvent :: JSVal }
instance PToJSVal ClipboardEvent where
pToJSVal = unClipboardEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal ClipboardEvent where
pFromJSVal = ClipboardEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal ClipboardEvent where
toJSVal = return . unClipboardEvent
{-# INLINE toJSVal #-}
instance FromJSVal ClipboardEvent where
fromJSVal v = fmap ClipboardEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ClipboardEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ClipboardEvent where
makeObject = makeObject . unClipboardEvent
instance IsEvent ClipboardEvent
instance IsGObject ClipboardEvent where
typeGType _ = gTypeClipboardEvent
{-# INLINE typeGType #-}
noClipboardEvent :: Maybe ClipboardEvent
noClipboardEvent = Nothing
{-# INLINE noClipboardEvent #-}
gTypeClipboardEvent :: JSM GType
gTypeClipboardEvent = GType . Object <$> jsg "ClipboardEvent"
newtype ClipboardEventInit = ClipboardEventInit { unClipboardEventInit :: JSVal }
instance PToJSVal ClipboardEventInit where
pToJSVal = unClipboardEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal ClipboardEventInit where
pFromJSVal = ClipboardEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal ClipboardEventInit where
toJSVal = return . unClipboardEventInit
{-# INLINE toJSVal #-}
instance FromJSVal ClipboardEventInit where
fromJSVal v = fmap ClipboardEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ClipboardEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ClipboardEventInit where
makeObject = makeObject . unClipboardEventInit
instance IsEventInit ClipboardEventInit
instance IsGObject ClipboardEventInit where
typeGType _ = gTypeClipboardEventInit
{-# INLINE typeGType #-}
noClipboardEventInit :: Maybe ClipboardEventInit
noClipboardEventInit = Nothing
{-# INLINE noClipboardEventInit #-}
gTypeClipboardEventInit :: JSM GType
gTypeClipboardEventInit = GType . Object <$> jsg "ClipboardEventInit"
newtype CloseEvent = CloseEvent { unCloseEvent :: JSVal }
instance PToJSVal CloseEvent where
pToJSVal = unCloseEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal CloseEvent where
pFromJSVal = CloseEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal CloseEvent where
toJSVal = return . unCloseEvent
{-# INLINE toJSVal #-}
instance FromJSVal CloseEvent where
fromJSVal v = fmap CloseEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CloseEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CloseEvent where
makeObject = makeObject . unCloseEvent
instance IsEvent CloseEvent
instance IsGObject CloseEvent where
typeGType _ = gTypeCloseEvent
{-# INLINE typeGType #-}
noCloseEvent :: Maybe CloseEvent
noCloseEvent = Nothing
{-# INLINE noCloseEvent #-}
gTypeCloseEvent :: JSM GType
gTypeCloseEvent = GType . Object <$> jsg "CloseEvent"
newtype CloseEventInit = CloseEventInit { unCloseEventInit :: JSVal }
instance PToJSVal CloseEventInit where
pToJSVal = unCloseEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal CloseEventInit where
pFromJSVal = CloseEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal CloseEventInit where
toJSVal = return . unCloseEventInit
{-# INLINE toJSVal #-}
instance FromJSVal CloseEventInit where
fromJSVal v = fmap CloseEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CloseEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CloseEventInit where
makeObject = makeObject . unCloseEventInit
instance IsEventInit CloseEventInit
instance IsGObject CloseEventInit where
typeGType _ = gTypeCloseEventInit
{-# INLINE typeGType #-}
noCloseEventInit :: Maybe CloseEventInit
noCloseEventInit = Nothing
{-# INLINE noCloseEventInit #-}
gTypeCloseEventInit :: JSM GType
gTypeCloseEventInit = GType . Object <$> jsg "CloseEventInit"
newtype CommandLineAPIHost = CommandLineAPIHost { unCommandLineAPIHost :: JSVal }
instance PToJSVal CommandLineAPIHost where
pToJSVal = unCommandLineAPIHost
{-# INLINE pToJSVal #-}
instance PFromJSVal CommandLineAPIHost where
pFromJSVal = CommandLineAPIHost
{-# INLINE pFromJSVal #-}
instance ToJSVal CommandLineAPIHost where
toJSVal = return . unCommandLineAPIHost
{-# INLINE toJSVal #-}
instance FromJSVal CommandLineAPIHost where
fromJSVal v = fmap CommandLineAPIHost <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CommandLineAPIHost
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CommandLineAPIHost where
makeObject = makeObject . unCommandLineAPIHost
instance IsGObject CommandLineAPIHost where
typeGType _ = gTypeCommandLineAPIHost
{-# INLINE typeGType #-}
noCommandLineAPIHost :: Maybe CommandLineAPIHost
noCommandLineAPIHost = Nothing
{-# INLINE noCommandLineAPIHost #-}
gTypeCommandLineAPIHost :: JSM GType
gTypeCommandLineAPIHost = GType . Object <$> jsg "CommandLineAPIHost"
newtype Comment = Comment { unComment :: JSVal }
instance PToJSVal Comment where
pToJSVal = unComment
{-# INLINE pToJSVal #-}
instance PFromJSVal Comment where
pFromJSVal = Comment
{-# INLINE pFromJSVal #-}
instance ToJSVal Comment where
toJSVal = return . unComment
{-# INLINE toJSVal #-}
instance FromJSVal Comment where
fromJSVal v = fmap Comment <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Comment
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Comment where
makeObject = makeObject . unComment
instance IsCharacterData Comment
instance IsNode Comment
instance IsEventTarget Comment
instance IsNonDocumentTypeChildNode Comment
instance IsChildNode Comment
instance IsGObject Comment where
typeGType _ = gTypeComment
{-# INLINE typeGType #-}
noComment :: Maybe Comment
noComment = Nothing
{-# INLINE noComment #-}
gTypeComment :: JSM GType
gTypeComment = GType . Object <$> jsg "Comment"
newtype CompositionEvent = CompositionEvent { unCompositionEvent :: JSVal }
instance PToJSVal CompositionEvent where
pToJSVal = unCompositionEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal CompositionEvent where
pFromJSVal = CompositionEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal CompositionEvent where
toJSVal = return . unCompositionEvent
{-# INLINE toJSVal #-}
instance FromJSVal CompositionEvent where
fromJSVal v = fmap CompositionEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CompositionEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CompositionEvent where
makeObject = makeObject . unCompositionEvent
instance IsUIEvent CompositionEvent
instance IsEvent CompositionEvent
instance IsGObject CompositionEvent where
typeGType _ = gTypeCompositionEvent
{-# INLINE typeGType #-}
noCompositionEvent :: Maybe CompositionEvent
noCompositionEvent = Nothing
{-# INLINE noCompositionEvent #-}
gTypeCompositionEvent :: JSM GType
gTypeCompositionEvent = GType . Object <$> jsg "CompositionEvent"
newtype CompositionEventInit = CompositionEventInit { unCompositionEventInit :: JSVal }
instance PToJSVal CompositionEventInit where
pToJSVal = unCompositionEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal CompositionEventInit where
pFromJSVal = CompositionEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal CompositionEventInit where
toJSVal = return . unCompositionEventInit
{-# INLINE toJSVal #-}
instance FromJSVal CompositionEventInit where
fromJSVal v = fmap CompositionEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CompositionEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CompositionEventInit where
makeObject = makeObject . unCompositionEventInit
instance IsUIEventInit CompositionEventInit
instance IsEventInit CompositionEventInit
instance IsGObject CompositionEventInit where
typeGType _ = gTypeCompositionEventInit
{-# INLINE typeGType #-}
noCompositionEventInit :: Maybe CompositionEventInit
noCompositionEventInit = Nothing
{-# INLINE noCompositionEventInit #-}
gTypeCompositionEventInit :: JSM GType
gTypeCompositionEventInit = GType . Object <$> jsg "CompositionEventInit"
newtype ConstrainBooleanParameters = ConstrainBooleanParameters { unConstrainBooleanParameters :: JSVal }
instance PToJSVal ConstrainBooleanParameters where
pToJSVal = unConstrainBooleanParameters
{-# INLINE pToJSVal #-}
instance PFromJSVal ConstrainBooleanParameters where
pFromJSVal = ConstrainBooleanParameters
{-# INLINE pFromJSVal #-}
instance ToJSVal ConstrainBooleanParameters where
toJSVal = return . unConstrainBooleanParameters
{-# INLINE toJSVal #-}
instance FromJSVal ConstrainBooleanParameters where
fromJSVal v = fmap ConstrainBooleanParameters <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ConstrainBooleanParameters
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ConstrainBooleanParameters where
makeObject = makeObject . unConstrainBooleanParameters
instance IsGObject ConstrainBooleanParameters where
typeGType _ = gTypeConstrainBooleanParameters
{-# INLINE typeGType #-}
noConstrainBooleanParameters :: Maybe ConstrainBooleanParameters
noConstrainBooleanParameters = Nothing
{-# INLINE noConstrainBooleanParameters #-}
gTypeConstrainBooleanParameters :: JSM GType
gTypeConstrainBooleanParameters = GType . Object <$> jsg "ConstrainBooleanParameters"
newtype ConstrainDOMStringParameters = ConstrainDOMStringParameters { unConstrainDOMStringParameters :: JSVal }
instance PToJSVal ConstrainDOMStringParameters where
pToJSVal = unConstrainDOMStringParameters
{-# INLINE pToJSVal #-}
instance PFromJSVal ConstrainDOMStringParameters where
pFromJSVal = ConstrainDOMStringParameters
{-# INLINE pFromJSVal #-}
instance ToJSVal ConstrainDOMStringParameters where
toJSVal = return . unConstrainDOMStringParameters
{-# INLINE toJSVal #-}
instance FromJSVal ConstrainDOMStringParameters where
fromJSVal v = fmap ConstrainDOMStringParameters <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ConstrainDOMStringParameters
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ConstrainDOMStringParameters where
makeObject = makeObject . unConstrainDOMStringParameters
instance IsGObject ConstrainDOMStringParameters where
typeGType _ = gTypeConstrainDOMStringParameters
{-# INLINE typeGType #-}
noConstrainDOMStringParameters :: Maybe ConstrainDOMStringParameters
noConstrainDOMStringParameters = Nothing
{-# INLINE noConstrainDOMStringParameters #-}
gTypeConstrainDOMStringParameters :: JSM GType
gTypeConstrainDOMStringParameters = GType . Object <$> jsg "ConstrainDOMStringParameters"
newtype ConstrainDoubleRange = ConstrainDoubleRange { unConstrainDoubleRange :: JSVal }
instance PToJSVal ConstrainDoubleRange where
pToJSVal = unConstrainDoubleRange
{-# INLINE pToJSVal #-}
instance PFromJSVal ConstrainDoubleRange where
pFromJSVal = ConstrainDoubleRange
{-# INLINE pFromJSVal #-}
instance ToJSVal ConstrainDoubleRange where
toJSVal = return . unConstrainDoubleRange
{-# INLINE toJSVal #-}
instance FromJSVal ConstrainDoubleRange where
fromJSVal v = fmap ConstrainDoubleRange <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ConstrainDoubleRange
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ConstrainDoubleRange where
makeObject = makeObject . unConstrainDoubleRange
instance IsDoubleRange ConstrainDoubleRange
instance IsGObject ConstrainDoubleRange where
typeGType _ = gTypeConstrainDoubleRange
{-# INLINE typeGType #-}
noConstrainDoubleRange :: Maybe ConstrainDoubleRange
noConstrainDoubleRange = Nothing
{-# INLINE noConstrainDoubleRange #-}
gTypeConstrainDoubleRange :: JSM GType
gTypeConstrainDoubleRange = GType . Object <$> jsg "ConstrainDoubleRange"
newtype ConstrainLongRange = ConstrainLongRange { unConstrainLongRange :: JSVal }
instance PToJSVal ConstrainLongRange where
pToJSVal = unConstrainLongRange
{-# INLINE pToJSVal #-}
instance PFromJSVal ConstrainLongRange where
pFromJSVal = ConstrainLongRange
{-# INLINE pFromJSVal #-}
instance ToJSVal ConstrainLongRange where
toJSVal = return . unConstrainLongRange
{-# INLINE toJSVal #-}
instance FromJSVal ConstrainLongRange where
fromJSVal v = fmap ConstrainLongRange <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ConstrainLongRange
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ConstrainLongRange where
makeObject = makeObject . unConstrainLongRange
instance IsLongRange ConstrainLongRange
instance IsGObject ConstrainLongRange where
typeGType _ = gTypeConstrainLongRange
{-# INLINE typeGType #-}
noConstrainLongRange :: Maybe ConstrainLongRange
noConstrainLongRange = Nothing
{-# INLINE noConstrainLongRange #-}
gTypeConstrainLongRange :: JSM GType
gTypeConstrainLongRange = GType . Object <$> jsg "ConstrainLongRange"
newtype ConvolverNode = ConvolverNode { unConvolverNode :: JSVal }
instance PToJSVal ConvolverNode where
pToJSVal = unConvolverNode
{-# INLINE pToJSVal #-}
instance PFromJSVal ConvolverNode where
pFromJSVal = ConvolverNode
{-# INLINE pFromJSVal #-}
instance ToJSVal ConvolverNode where
toJSVal = return . unConvolverNode
{-# INLINE toJSVal #-}
instance FromJSVal ConvolverNode where
fromJSVal v = fmap ConvolverNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ConvolverNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ConvolverNode where
makeObject = makeObject . unConvolverNode
instance IsAudioNode ConvolverNode
instance IsEventTarget ConvolverNode
instance IsGObject ConvolverNode where
typeGType _ = gTypeConvolverNode
{-# INLINE typeGType #-}
noConvolverNode :: Maybe ConvolverNode
noConvolverNode = Nothing
{-# INLINE noConvolverNode #-}
gTypeConvolverNode :: JSM GType
gTypeConvolverNode = GType . Object <$> jsg "ConvolverNode"
newtype Coordinates = Coordinates { unCoordinates :: JSVal }
instance PToJSVal Coordinates where
pToJSVal = unCoordinates
{-# INLINE pToJSVal #-}
instance PFromJSVal Coordinates where
pFromJSVal = Coordinates
{-# INLINE pFromJSVal #-}
instance ToJSVal Coordinates where
toJSVal = return . unCoordinates
{-# INLINE toJSVal #-}
instance FromJSVal Coordinates where
fromJSVal v = fmap Coordinates <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Coordinates
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Coordinates where
makeObject = makeObject . unCoordinates
instance IsGObject Coordinates where
typeGType _ = gTypeCoordinates
{-# INLINE typeGType #-}
noCoordinates :: Maybe Coordinates
noCoordinates = Nothing
{-# INLINE noCoordinates #-}
gTypeCoordinates :: JSM GType
gTypeCoordinates = GType . Object <$> jsg "Coordinates"
newtype CountQueuingStrategy = CountQueuingStrategy { unCountQueuingStrategy :: JSVal }
instance PToJSVal CountQueuingStrategy where
pToJSVal = unCountQueuingStrategy
{-# INLINE pToJSVal #-}
instance PFromJSVal CountQueuingStrategy where
pFromJSVal = CountQueuingStrategy
{-# INLINE pFromJSVal #-}
instance ToJSVal CountQueuingStrategy where
toJSVal = return . unCountQueuingStrategy
{-# INLINE toJSVal #-}
instance FromJSVal CountQueuingStrategy where
fromJSVal v = fmap CountQueuingStrategy <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CountQueuingStrategy
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CountQueuingStrategy where
makeObject = makeObject . unCountQueuingStrategy
instance IsGObject CountQueuingStrategy where
typeGType _ = gTypeCountQueuingStrategy
{-# INLINE typeGType #-}
noCountQueuingStrategy :: Maybe CountQueuingStrategy
noCountQueuingStrategy = Nothing
{-# INLINE noCountQueuingStrategy #-}
gTypeCountQueuingStrategy :: JSM GType
gTypeCountQueuingStrategy = GType . Object <$> jsg "CountQueuingStrategy"
newtype Counter = Counter { unCounter :: JSVal }
instance PToJSVal Counter where
pToJSVal = unCounter
{-# INLINE pToJSVal #-}
instance PFromJSVal Counter where
pFromJSVal = Counter
{-# INLINE pFromJSVal #-}
instance ToJSVal Counter where
toJSVal = return . unCounter
{-# INLINE toJSVal #-}
instance FromJSVal Counter where
fromJSVal v = fmap Counter <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Counter
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Counter where
makeObject = makeObject . unCounter
instance IsGObject Counter where
typeGType _ = gTypeCounter
{-# INLINE typeGType #-}
noCounter :: Maybe Counter
noCounter = Nothing
{-# INLINE noCounter #-}
gTypeCounter :: JSM GType
gTypeCounter = GType . Object <$> jsg "Counter"
newtype CredentialData = CredentialData { unCredentialData :: JSVal }
instance PToJSVal CredentialData where
pToJSVal = unCredentialData
{-# INLINE pToJSVal #-}
instance PFromJSVal CredentialData where
pFromJSVal = CredentialData
{-# INLINE pFromJSVal #-}
instance ToJSVal CredentialData where
toJSVal = return . unCredentialData
{-# INLINE toJSVal #-}
instance FromJSVal CredentialData where
fromJSVal v = fmap CredentialData <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CredentialData
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CredentialData where
makeObject = makeObject . unCredentialData
class (IsGObject o) => IsCredentialData o
toCredentialData :: IsCredentialData o => o -> CredentialData
toCredentialData = CredentialData . coerce
instance IsCredentialData CredentialData
instance IsGObject CredentialData where
typeGType _ = gTypeCredentialData
{-# INLINE typeGType #-}
noCredentialData :: Maybe CredentialData
noCredentialData = Nothing
{-# INLINE noCredentialData #-}
gTypeCredentialData :: JSM GType
gTypeCredentialData = GType . Object <$> jsg "CredentialData"
newtype Crypto = Crypto { unCrypto :: JSVal }
instance PToJSVal Crypto where
pToJSVal = unCrypto
{-# INLINE pToJSVal #-}
instance PFromJSVal Crypto where
pFromJSVal = Crypto
{-# INLINE pFromJSVal #-}
instance ToJSVal Crypto where
toJSVal = return . unCrypto
{-# INLINE toJSVal #-}
instance FromJSVal Crypto where
fromJSVal v = fmap Crypto <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Crypto
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Crypto where
makeObject = makeObject . unCrypto
instance IsGObject Crypto where
typeGType _ = gTypeCrypto
{-# INLINE typeGType #-}
noCrypto :: Maybe Crypto
noCrypto = Nothing
{-# INLINE noCrypto #-}
gTypeCrypto :: JSM GType
gTypeCrypto = GType . Object <$> jsg "Crypto"
newtype CryptoAlgorithmParameters = CryptoAlgorithmParameters { unCryptoAlgorithmParameters :: JSVal }
instance PToJSVal CryptoAlgorithmParameters where
pToJSVal = unCryptoAlgorithmParameters
{-# INLINE pToJSVal #-}
instance PFromJSVal CryptoAlgorithmParameters where
pFromJSVal = CryptoAlgorithmParameters
{-# INLINE pFromJSVal #-}
instance ToJSVal CryptoAlgorithmParameters where
toJSVal = return . unCryptoAlgorithmParameters
{-# INLINE toJSVal #-}
instance FromJSVal CryptoAlgorithmParameters where
fromJSVal v = fmap CryptoAlgorithmParameters <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CryptoAlgorithmParameters
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CryptoAlgorithmParameters where
makeObject = makeObject . unCryptoAlgorithmParameters
class (IsGObject o) => IsCryptoAlgorithmParameters o
toCryptoAlgorithmParameters :: IsCryptoAlgorithmParameters o => o -> CryptoAlgorithmParameters
toCryptoAlgorithmParameters = CryptoAlgorithmParameters . coerce
instance IsCryptoAlgorithmParameters CryptoAlgorithmParameters
instance IsGObject CryptoAlgorithmParameters where
typeGType _ = gTypeCryptoAlgorithmParameters
{-# INLINE typeGType #-}
noCryptoAlgorithmParameters :: Maybe CryptoAlgorithmParameters
noCryptoAlgorithmParameters = Nothing
{-# INLINE noCryptoAlgorithmParameters #-}
gTypeCryptoAlgorithmParameters :: JSM GType
gTypeCryptoAlgorithmParameters = GType . Object <$> jsg "CryptoAlgorithmParameters"
newtype CryptoKey = CryptoKey { unCryptoKey :: JSVal }
instance PToJSVal CryptoKey where
pToJSVal = unCryptoKey
{-# INLINE pToJSVal #-}
instance PFromJSVal CryptoKey where
pFromJSVal = CryptoKey
{-# INLINE pFromJSVal #-}
instance ToJSVal CryptoKey where
toJSVal = return . unCryptoKey
{-# INLINE toJSVal #-}
instance FromJSVal CryptoKey where
fromJSVal v = fmap CryptoKey <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CryptoKey
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CryptoKey where
makeObject = makeObject . unCryptoKey
instance IsGObject CryptoKey where
typeGType _ = gTypeCryptoKey
{-# INLINE typeGType #-}
noCryptoKey :: Maybe CryptoKey
noCryptoKey = Nothing
{-# INLINE noCryptoKey #-}
gTypeCryptoKey :: JSM GType
gTypeCryptoKey = GType . Object <$> jsg "CryptoKey"
newtype CryptoKeyPair = CryptoKeyPair { unCryptoKeyPair :: JSVal }
instance PToJSVal CryptoKeyPair where
pToJSVal = unCryptoKeyPair
{-# INLINE pToJSVal #-}
instance PFromJSVal CryptoKeyPair where
pFromJSVal = CryptoKeyPair
{-# INLINE pFromJSVal #-}
instance ToJSVal CryptoKeyPair where
toJSVal = return . unCryptoKeyPair
{-# INLINE toJSVal #-}
instance FromJSVal CryptoKeyPair where
fromJSVal v = fmap CryptoKeyPair <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CryptoKeyPair
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CryptoKeyPair where
makeObject = makeObject . unCryptoKeyPair
instance IsGObject CryptoKeyPair where
typeGType _ = gTypeCryptoKeyPair
{-# INLINE typeGType #-}
noCryptoKeyPair :: Maybe CryptoKeyPair
noCryptoKeyPair = Nothing
{-# INLINE noCryptoKeyPair #-}
gTypeCryptoKeyPair :: JSM GType
gTypeCryptoKeyPair = GType . Object <$> jsg "CryptoKeyPair"
newtype CustomElementRegistry = CustomElementRegistry { unCustomElementRegistry :: JSVal }
instance PToJSVal CustomElementRegistry where
pToJSVal = unCustomElementRegistry
{-# INLINE pToJSVal #-}
instance PFromJSVal CustomElementRegistry where
pFromJSVal = CustomElementRegistry
{-# INLINE pFromJSVal #-}
instance ToJSVal CustomElementRegistry where
toJSVal = return . unCustomElementRegistry
{-# INLINE toJSVal #-}
instance FromJSVal CustomElementRegistry where
fromJSVal v = fmap CustomElementRegistry <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CustomElementRegistry
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CustomElementRegistry where
makeObject = makeObject . unCustomElementRegistry
instance IsGObject CustomElementRegistry where
typeGType _ = gTypeCustomElementRegistry
{-# INLINE typeGType #-}
noCustomElementRegistry :: Maybe CustomElementRegistry
noCustomElementRegistry = Nothing
{-# INLINE noCustomElementRegistry #-}
gTypeCustomElementRegistry :: JSM GType
gTypeCustomElementRegistry = GType . Object <$> jsg "CustomElementRegistry"
newtype CustomEvent = CustomEvent { unCustomEvent :: JSVal }
instance PToJSVal CustomEvent where
pToJSVal = unCustomEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal CustomEvent where
pFromJSVal = CustomEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal CustomEvent where
toJSVal = return . unCustomEvent
{-# INLINE toJSVal #-}
instance FromJSVal CustomEvent where
fromJSVal v = fmap CustomEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CustomEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CustomEvent where
makeObject = makeObject . unCustomEvent
instance IsEvent CustomEvent
instance IsGObject CustomEvent where
typeGType _ = gTypeCustomEvent
{-# INLINE typeGType #-}
noCustomEvent :: Maybe CustomEvent
noCustomEvent = Nothing
{-# INLINE noCustomEvent #-}
gTypeCustomEvent :: JSM GType
gTypeCustomEvent = GType . Object <$> jsg "CustomEvent"
newtype CustomEventInit = CustomEventInit { unCustomEventInit :: JSVal }
instance PToJSVal CustomEventInit where
pToJSVal = unCustomEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal CustomEventInit where
pFromJSVal = CustomEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal CustomEventInit where
toJSVal = return . unCustomEventInit
{-# INLINE toJSVal #-}
instance FromJSVal CustomEventInit where
fromJSVal v = fmap CustomEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . CustomEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject CustomEventInit where
makeObject = makeObject . unCustomEventInit
instance IsEventInit CustomEventInit
instance IsGObject CustomEventInit where
typeGType _ = gTypeCustomEventInit
{-# INLINE typeGType #-}
noCustomEventInit :: Maybe CustomEventInit
noCustomEventInit = Nothing
{-# INLINE noCustomEventInit #-}
gTypeCustomEventInit :: JSM GType
gTypeCustomEventInit = GType . Object <$> jsg "CustomEventInit"
newtype DOMError = DOMError { unDOMError :: JSVal }
instance PToJSVal DOMError where
pToJSVal = unDOMError
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMError where
pFromJSVal = DOMError
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMError where
toJSVal = return . unDOMError
{-# INLINE toJSVal #-}
instance FromJSVal DOMError where
fromJSVal v = fmap DOMError <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMError
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMError where
makeObject = makeObject . unDOMError
class (IsGObject o) => IsDOMError o
toDOMError :: IsDOMError o => o -> DOMError
toDOMError = DOMError . coerce
instance IsDOMError DOMError
instance IsGObject DOMError where
typeGType _ = gTypeDOMError
{-# INLINE typeGType #-}
noDOMError :: Maybe DOMError
noDOMError = Nothing
{-# INLINE noDOMError #-}
gTypeDOMError :: JSM GType
gTypeDOMError = GType . Object <$> jsg "DOMError"
newtype DOMException = DOMException { unDOMException :: JSVal }
instance PToJSVal DOMException where
pToJSVal = unDOMException
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMException where
pFromJSVal = DOMException
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMException where
toJSVal = return . unDOMException
{-# INLINE toJSVal #-}
instance FromJSVal DOMException where
fromJSVal v = fmap DOMException <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMException
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMException where
makeObject = makeObject . unDOMException
instance IsGObject DOMException where
typeGType _ = gTypeDOMException
{-# INLINE typeGType #-}
noDOMException :: Maybe DOMException
noDOMException = Nothing
{-# INLINE noDOMException #-}
gTypeDOMException :: JSM GType
gTypeDOMException = GType . Object <$> jsg "DOMException"
newtype DOMImplementation = DOMImplementation { unDOMImplementation :: JSVal }
instance PToJSVal DOMImplementation where
pToJSVal = unDOMImplementation
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMImplementation where
pFromJSVal = DOMImplementation
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMImplementation where
toJSVal = return . unDOMImplementation
{-# INLINE toJSVal #-}
instance FromJSVal DOMImplementation where
fromJSVal v = fmap DOMImplementation <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMImplementation
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMImplementation where
makeObject = makeObject . unDOMImplementation
instance IsGObject DOMImplementation where
typeGType _ = gTypeDOMImplementation
{-# INLINE typeGType #-}
noDOMImplementation :: Maybe DOMImplementation
noDOMImplementation = Nothing
{-# INLINE noDOMImplementation #-}
gTypeDOMImplementation :: JSM GType
gTypeDOMImplementation = GType . Object <$> jsg "DOMImplementation"
newtype DOMNamedFlowCollection = DOMNamedFlowCollection { unDOMNamedFlowCollection :: JSVal }
instance PToJSVal DOMNamedFlowCollection where
pToJSVal = unDOMNamedFlowCollection
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMNamedFlowCollection where
pFromJSVal = DOMNamedFlowCollection
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMNamedFlowCollection where
toJSVal = return . unDOMNamedFlowCollection
{-# INLINE toJSVal #-}
instance FromJSVal DOMNamedFlowCollection where
fromJSVal v = fmap DOMNamedFlowCollection <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMNamedFlowCollection
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMNamedFlowCollection where
makeObject = makeObject . unDOMNamedFlowCollection
instance IsGObject DOMNamedFlowCollection where
typeGType _ = gTypeDOMNamedFlowCollection
{-# INLINE typeGType #-}
noDOMNamedFlowCollection :: Maybe DOMNamedFlowCollection
noDOMNamedFlowCollection = Nothing
{-# INLINE noDOMNamedFlowCollection #-}
gTypeDOMNamedFlowCollection :: JSM GType
gTypeDOMNamedFlowCollection = GType . Object <$> jsg "WebKitNamedFlowCollection"
newtype DOMParser = DOMParser { unDOMParser :: JSVal }
instance PToJSVal DOMParser where
pToJSVal = unDOMParser
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMParser where
pFromJSVal = DOMParser
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMParser where
toJSVal = return . unDOMParser
{-# INLINE toJSVal #-}
instance FromJSVal DOMParser where
fromJSVal v = fmap DOMParser <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMParser
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMParser where
makeObject = makeObject . unDOMParser
instance IsGObject DOMParser where
typeGType _ = gTypeDOMParser
{-# INLINE typeGType #-}
noDOMParser :: Maybe DOMParser
noDOMParser = Nothing
{-# INLINE noDOMParser #-}
gTypeDOMParser :: JSM GType
gTypeDOMParser = GType . Object <$> jsg "DOMParser"
newtype DOMPoint = DOMPoint { unDOMPoint :: JSVal }
instance PToJSVal DOMPoint where
pToJSVal = unDOMPoint
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMPoint where
pFromJSVal = DOMPoint
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMPoint where
toJSVal = return . unDOMPoint
{-# INLINE toJSVal #-}
instance FromJSVal DOMPoint where
fromJSVal v = fmap DOMPoint <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMPoint
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMPoint where
makeObject = makeObject . unDOMPoint
instance IsDOMPointReadOnly DOMPoint
instance IsGObject DOMPoint where
typeGType _ = gTypeDOMPoint
{-# INLINE typeGType #-}
noDOMPoint :: Maybe DOMPoint
noDOMPoint = Nothing
{-# INLINE noDOMPoint #-}
gTypeDOMPoint :: JSM GType
gTypeDOMPoint = GType . Object <$> jsg "DOMPoint"
newtype DOMPointInit = DOMPointInit { unDOMPointInit :: JSVal }
instance PToJSVal DOMPointInit where
pToJSVal = unDOMPointInit
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMPointInit where
pFromJSVal = DOMPointInit
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMPointInit where
toJSVal = return . unDOMPointInit
{-# INLINE toJSVal #-}
instance FromJSVal DOMPointInit where
fromJSVal v = fmap DOMPointInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMPointInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMPointInit where
makeObject = makeObject . unDOMPointInit
instance IsGObject DOMPointInit where
typeGType _ = gTypeDOMPointInit
{-# INLINE typeGType #-}
noDOMPointInit :: Maybe DOMPointInit
noDOMPointInit = Nothing
{-# INLINE noDOMPointInit #-}
gTypeDOMPointInit :: JSM GType
gTypeDOMPointInit = GType . Object <$> jsg "DOMPointInit"
newtype DOMPointReadOnly = DOMPointReadOnly { unDOMPointReadOnly :: JSVal }
instance PToJSVal DOMPointReadOnly where
pToJSVal = unDOMPointReadOnly
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMPointReadOnly where
pFromJSVal = DOMPointReadOnly
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMPointReadOnly where
toJSVal = return . unDOMPointReadOnly
{-# INLINE toJSVal #-}
instance FromJSVal DOMPointReadOnly where
fromJSVal v = fmap DOMPointReadOnly <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMPointReadOnly
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMPointReadOnly where
makeObject = makeObject . unDOMPointReadOnly
class (IsGObject o) => IsDOMPointReadOnly o
toDOMPointReadOnly :: IsDOMPointReadOnly o => o -> DOMPointReadOnly
toDOMPointReadOnly = DOMPointReadOnly . coerce
instance IsDOMPointReadOnly DOMPointReadOnly
instance IsGObject DOMPointReadOnly where
typeGType _ = gTypeDOMPointReadOnly
{-# INLINE typeGType #-}
noDOMPointReadOnly :: Maybe DOMPointReadOnly
noDOMPointReadOnly = Nothing
{-# INLINE noDOMPointReadOnly #-}
gTypeDOMPointReadOnly :: JSM GType
gTypeDOMPointReadOnly = GType . Object <$> jsg "DOMPointReadOnly"
newtype DOMRect = DOMRect { unDOMRect :: JSVal }
instance PToJSVal DOMRect where
pToJSVal = unDOMRect
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMRect where
pFromJSVal = DOMRect
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMRect where
toJSVal = return . unDOMRect
{-# INLINE toJSVal #-}
instance FromJSVal DOMRect where
fromJSVal v = fmap DOMRect <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMRect
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMRect where
makeObject = makeObject . unDOMRect
instance IsDOMRectReadOnly DOMRect
instance IsGObject DOMRect where
typeGType _ = gTypeDOMRect
{-# INLINE typeGType #-}
noDOMRect :: Maybe DOMRect
noDOMRect = Nothing
{-# INLINE noDOMRect #-}
gTypeDOMRect :: JSM GType
gTypeDOMRect = GType . Object <$> jsg "DOMRect"
newtype DOMRectInit = DOMRectInit { unDOMRectInit :: JSVal }
instance PToJSVal DOMRectInit where
pToJSVal = unDOMRectInit
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMRectInit where
pFromJSVal = DOMRectInit
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMRectInit where
toJSVal = return . unDOMRectInit
{-# INLINE toJSVal #-}
instance FromJSVal DOMRectInit where
fromJSVal v = fmap DOMRectInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMRectInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMRectInit where
makeObject = makeObject . unDOMRectInit
instance IsGObject DOMRectInit where
typeGType _ = gTypeDOMRectInit
{-# INLINE typeGType #-}
noDOMRectInit :: Maybe DOMRectInit
noDOMRectInit = Nothing
{-# INLINE noDOMRectInit #-}
gTypeDOMRectInit :: JSM GType
gTypeDOMRectInit = GType . Object <$> jsg "DOMRectInit"
newtype DOMRectReadOnly = DOMRectReadOnly { unDOMRectReadOnly :: JSVal }
instance PToJSVal DOMRectReadOnly where
pToJSVal = unDOMRectReadOnly
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMRectReadOnly where
pFromJSVal = DOMRectReadOnly
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMRectReadOnly where
toJSVal = return . unDOMRectReadOnly
{-# INLINE toJSVal #-}
instance FromJSVal DOMRectReadOnly where
fromJSVal v = fmap DOMRectReadOnly <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMRectReadOnly
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMRectReadOnly where
makeObject = makeObject . unDOMRectReadOnly
class (IsGObject o) => IsDOMRectReadOnly o
toDOMRectReadOnly :: IsDOMRectReadOnly o => o -> DOMRectReadOnly
toDOMRectReadOnly = DOMRectReadOnly . coerce
instance IsDOMRectReadOnly DOMRectReadOnly
instance IsGObject DOMRectReadOnly where
typeGType _ = gTypeDOMRectReadOnly
{-# INLINE typeGType #-}
noDOMRectReadOnly :: Maybe DOMRectReadOnly
noDOMRectReadOnly = Nothing
{-# INLINE noDOMRectReadOnly #-}
gTypeDOMRectReadOnly :: JSM GType
gTypeDOMRectReadOnly = GType . Object <$> jsg "DOMRectReadOnly"
newtype DOMStringList = DOMStringList { unDOMStringList :: JSVal }
instance PToJSVal DOMStringList where
pToJSVal = unDOMStringList
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMStringList where
pFromJSVal = DOMStringList
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMStringList where
toJSVal = return . unDOMStringList
{-# INLINE toJSVal #-}
instance FromJSVal DOMStringList where
fromJSVal v = fmap DOMStringList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMStringList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMStringList where
makeObject = makeObject . unDOMStringList
instance IsGObject DOMStringList where
typeGType _ = gTypeDOMStringList
{-# INLINE typeGType #-}
noDOMStringList :: Maybe DOMStringList
noDOMStringList = Nothing
{-# INLINE noDOMStringList #-}
gTypeDOMStringList :: JSM GType
gTypeDOMStringList = GType . Object <$> jsg "DOMStringList"
newtype DOMStringMap = DOMStringMap { unDOMStringMap :: JSVal }
instance PToJSVal DOMStringMap where
pToJSVal = unDOMStringMap
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMStringMap where
pFromJSVal = DOMStringMap
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMStringMap where
toJSVal = return . unDOMStringMap
{-# INLINE toJSVal #-}
instance FromJSVal DOMStringMap where
fromJSVal v = fmap DOMStringMap <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMStringMap
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMStringMap where
makeObject = makeObject . unDOMStringMap
instance IsGObject DOMStringMap where
typeGType _ = gTypeDOMStringMap
{-# INLINE typeGType #-}
noDOMStringMap :: Maybe DOMStringMap
noDOMStringMap = Nothing
{-# INLINE noDOMStringMap #-}
gTypeDOMStringMap :: JSM GType
gTypeDOMStringMap = GType . Object <$> jsg "DOMStringMap"
newtype DOMTokenList = DOMTokenList { unDOMTokenList :: JSVal }
instance PToJSVal DOMTokenList where
pToJSVal = unDOMTokenList
{-# INLINE pToJSVal #-}
instance PFromJSVal DOMTokenList where
pFromJSVal = DOMTokenList
{-# INLINE pFromJSVal #-}
instance ToJSVal DOMTokenList where
toJSVal = return . unDOMTokenList
{-# INLINE toJSVal #-}
instance FromJSVal DOMTokenList where
fromJSVal v = fmap DOMTokenList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DOMTokenList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DOMTokenList where
makeObject = makeObject . unDOMTokenList
instance IsGObject DOMTokenList where
typeGType _ = gTypeDOMTokenList
{-# INLINE typeGType #-}
noDOMTokenList :: Maybe DOMTokenList
noDOMTokenList = Nothing
{-# INLINE noDOMTokenList #-}
gTypeDOMTokenList :: JSM GType
gTypeDOMTokenList = GType . Object <$> jsg "DOMTokenList"
newtype DataCue = DataCue { unDataCue :: JSVal }
instance PToJSVal DataCue where
pToJSVal = unDataCue
{-# INLINE pToJSVal #-}
instance PFromJSVal DataCue where
pFromJSVal = DataCue
{-# INLINE pFromJSVal #-}
instance ToJSVal DataCue where
toJSVal = return . unDataCue
{-# INLINE toJSVal #-}
instance FromJSVal DataCue where
fromJSVal v = fmap DataCue <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DataCue
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DataCue where
makeObject = makeObject . unDataCue
instance IsTextTrackCue DataCue
instance IsEventTarget DataCue
instance IsGObject DataCue where
typeGType _ = gTypeDataCue
{-# INLINE typeGType #-}
noDataCue :: Maybe DataCue
noDataCue = Nothing
{-# INLINE noDataCue #-}
gTypeDataCue :: JSM GType
gTypeDataCue = GType . Object <$> jsg "WebKitDataCue"
newtype DataTransfer = DataTransfer { unDataTransfer :: JSVal }
instance PToJSVal DataTransfer where
pToJSVal = unDataTransfer
{-# INLINE pToJSVal #-}
instance PFromJSVal DataTransfer where
pFromJSVal = DataTransfer
{-# INLINE pFromJSVal #-}
instance ToJSVal DataTransfer where
toJSVal = return . unDataTransfer
{-# INLINE toJSVal #-}
instance FromJSVal DataTransfer where
fromJSVal v = fmap DataTransfer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DataTransfer
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DataTransfer where
makeObject = makeObject . unDataTransfer
instance IsGObject DataTransfer where
typeGType _ = gTypeDataTransfer
{-# INLINE typeGType #-}
noDataTransfer :: Maybe DataTransfer
noDataTransfer = Nothing
{-# INLINE noDataTransfer #-}
gTypeDataTransfer :: JSM GType
gTypeDataTransfer = GType . Object <$> jsg "DataTransfer"
newtype DataTransferItem = DataTransferItem { unDataTransferItem :: JSVal }
instance PToJSVal DataTransferItem where
pToJSVal = unDataTransferItem
{-# INLINE pToJSVal #-}
instance PFromJSVal DataTransferItem where
pFromJSVal = DataTransferItem
{-# INLINE pFromJSVal #-}
instance ToJSVal DataTransferItem where
toJSVal = return . unDataTransferItem
{-# INLINE toJSVal #-}
instance FromJSVal DataTransferItem where
fromJSVal v = fmap DataTransferItem <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DataTransferItem
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DataTransferItem where
makeObject = makeObject . unDataTransferItem
instance IsGObject DataTransferItem where
typeGType _ = gTypeDataTransferItem
{-# INLINE typeGType #-}
noDataTransferItem :: Maybe DataTransferItem
noDataTransferItem = Nothing
{-# INLINE noDataTransferItem #-}
gTypeDataTransferItem :: JSM GType
gTypeDataTransferItem = GType . Object <$> jsg "DataTransferItem"
newtype DataTransferItemList = DataTransferItemList { unDataTransferItemList :: JSVal }
instance PToJSVal DataTransferItemList where
pToJSVal = unDataTransferItemList
{-# INLINE pToJSVal #-}
instance PFromJSVal DataTransferItemList where
pFromJSVal = DataTransferItemList
{-# INLINE pFromJSVal #-}
instance ToJSVal DataTransferItemList where
toJSVal = return . unDataTransferItemList
{-# INLINE toJSVal #-}
instance FromJSVal DataTransferItemList where
fromJSVal v = fmap DataTransferItemList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DataTransferItemList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DataTransferItemList where
makeObject = makeObject . unDataTransferItemList
instance IsGObject DataTransferItemList where
typeGType _ = gTypeDataTransferItemList
{-# INLINE typeGType #-}
noDataTransferItemList :: Maybe DataTransferItemList
noDataTransferItemList = Nothing
{-# INLINE noDataTransferItemList #-}
gTypeDataTransferItemList :: JSM GType
gTypeDataTransferItemList = GType . Object <$> jsg "DataTransferItemList"
newtype Database = Database { unDatabase :: JSVal }
instance PToJSVal Database where
pToJSVal = unDatabase
{-# INLINE pToJSVal #-}
instance PFromJSVal Database where
pFromJSVal = Database
{-# INLINE pFromJSVal #-}
instance ToJSVal Database where
toJSVal = return . unDatabase
{-# INLINE toJSVal #-}
instance FromJSVal Database where
fromJSVal v = fmap Database <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Database
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Database where
makeObject = makeObject . unDatabase
instance IsGObject Database where
typeGType _ = gTypeDatabase
{-# INLINE typeGType #-}
noDatabase :: Maybe Database
noDatabase = Nothing
{-# INLINE noDatabase #-}
gTypeDatabase :: JSM GType
gTypeDatabase = GType . Object <$> jsg "Database"
newtype DedicatedWorkerGlobalScope = DedicatedWorkerGlobalScope { unDedicatedWorkerGlobalScope :: JSVal }
instance PToJSVal DedicatedWorkerGlobalScope where
pToJSVal = unDedicatedWorkerGlobalScope
{-# INLINE pToJSVal #-}
instance PFromJSVal DedicatedWorkerGlobalScope where
pFromJSVal = DedicatedWorkerGlobalScope
{-# INLINE pFromJSVal #-}
instance ToJSVal DedicatedWorkerGlobalScope where
toJSVal = return . unDedicatedWorkerGlobalScope
{-# INLINE toJSVal #-}
instance FromJSVal DedicatedWorkerGlobalScope where
fromJSVal v = fmap DedicatedWorkerGlobalScope <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DedicatedWorkerGlobalScope
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DedicatedWorkerGlobalScope where
makeObject = makeObject . unDedicatedWorkerGlobalScope
instance IsWorkerGlobalScope DedicatedWorkerGlobalScope
instance IsEventTarget DedicatedWorkerGlobalScope
instance IsWindowOrWorkerGlobalScope DedicatedWorkerGlobalScope
instance IsGlobalPerformance DedicatedWorkerGlobalScope
instance IsGlobalCrypto DedicatedWorkerGlobalScope
instance IsGObject DedicatedWorkerGlobalScope where
typeGType _ = gTypeDedicatedWorkerGlobalScope
{-# INLINE typeGType #-}
noDedicatedWorkerGlobalScope :: Maybe DedicatedWorkerGlobalScope
noDedicatedWorkerGlobalScope = Nothing
{-# INLINE noDedicatedWorkerGlobalScope #-}
gTypeDedicatedWorkerGlobalScope :: JSM GType
gTypeDedicatedWorkerGlobalScope = GType . Object <$> jsg "DedicatedWorkerGlobalScope"
newtype DelayNode = DelayNode { unDelayNode :: JSVal }
instance PToJSVal DelayNode where
pToJSVal = unDelayNode
{-# INLINE pToJSVal #-}
instance PFromJSVal DelayNode where
pFromJSVal = DelayNode
{-# INLINE pFromJSVal #-}
instance ToJSVal DelayNode where
toJSVal = return . unDelayNode
{-# INLINE toJSVal #-}
instance FromJSVal DelayNode where
fromJSVal v = fmap DelayNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DelayNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DelayNode where
makeObject = makeObject . unDelayNode
instance IsAudioNode DelayNode
instance IsEventTarget DelayNode
instance IsGObject DelayNode where
typeGType _ = gTypeDelayNode
{-# INLINE typeGType #-}
noDelayNode :: Maybe DelayNode
noDelayNode = Nothing
{-# INLINE noDelayNode #-}
gTypeDelayNode :: JSM GType
gTypeDelayNode = GType . Object <$> jsg "DelayNode"
newtype DeviceMotionEvent = DeviceMotionEvent { unDeviceMotionEvent :: JSVal }
instance PToJSVal DeviceMotionEvent where
pToJSVal = unDeviceMotionEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal DeviceMotionEvent where
pFromJSVal = DeviceMotionEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal DeviceMotionEvent where
toJSVal = return . unDeviceMotionEvent
{-# INLINE toJSVal #-}
instance FromJSVal DeviceMotionEvent where
fromJSVal v = fmap DeviceMotionEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DeviceMotionEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DeviceMotionEvent where
makeObject = makeObject . unDeviceMotionEvent
instance IsEvent DeviceMotionEvent
instance IsGObject DeviceMotionEvent where
typeGType _ = gTypeDeviceMotionEvent
{-# INLINE typeGType #-}
noDeviceMotionEvent :: Maybe DeviceMotionEvent
noDeviceMotionEvent = Nothing
{-# INLINE noDeviceMotionEvent #-}
gTypeDeviceMotionEvent :: JSM GType
gTypeDeviceMotionEvent = GType . Object <$> jsg "DeviceMotionEvent"
newtype DeviceOrientationEvent = DeviceOrientationEvent { unDeviceOrientationEvent :: JSVal }
instance PToJSVal DeviceOrientationEvent where
pToJSVal = unDeviceOrientationEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal DeviceOrientationEvent where
pFromJSVal = DeviceOrientationEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal DeviceOrientationEvent where
toJSVal = return . unDeviceOrientationEvent
{-# INLINE toJSVal #-}
instance FromJSVal DeviceOrientationEvent where
fromJSVal v = fmap DeviceOrientationEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DeviceOrientationEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DeviceOrientationEvent where
makeObject = makeObject . unDeviceOrientationEvent
instance IsEvent DeviceOrientationEvent
instance IsGObject DeviceOrientationEvent where
typeGType _ = gTypeDeviceOrientationEvent
{-# INLINE typeGType #-}
noDeviceOrientationEvent :: Maybe DeviceOrientationEvent
noDeviceOrientationEvent = Nothing
{-# INLINE noDeviceOrientationEvent #-}
gTypeDeviceOrientationEvent :: JSM GType
gTypeDeviceOrientationEvent = GType . Object <$> jsg "DeviceOrientationEvent"
newtype DeviceProximityEvent = DeviceProximityEvent { unDeviceProximityEvent :: JSVal }
instance PToJSVal DeviceProximityEvent where
pToJSVal = unDeviceProximityEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal DeviceProximityEvent where
pFromJSVal = DeviceProximityEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal DeviceProximityEvent where
toJSVal = return . unDeviceProximityEvent
{-# INLINE toJSVal #-}
instance FromJSVal DeviceProximityEvent where
fromJSVal v = fmap DeviceProximityEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DeviceProximityEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DeviceProximityEvent where
makeObject = makeObject . unDeviceProximityEvent
instance IsEvent DeviceProximityEvent
instance IsGObject DeviceProximityEvent where
typeGType _ = gTypeDeviceProximityEvent
{-# INLINE typeGType #-}
noDeviceProximityEvent :: Maybe DeviceProximityEvent
noDeviceProximityEvent = Nothing
{-# INLINE noDeviceProximityEvent #-}
gTypeDeviceProximityEvent :: JSM GType
gTypeDeviceProximityEvent = GType . Object <$> jsg "DeviceProximityEvent"
newtype DeviceProximityEventInit = DeviceProximityEventInit { unDeviceProximityEventInit :: JSVal }
instance PToJSVal DeviceProximityEventInit where
pToJSVal = unDeviceProximityEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal DeviceProximityEventInit where
pFromJSVal = DeviceProximityEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal DeviceProximityEventInit where
toJSVal = return . unDeviceProximityEventInit
{-# INLINE toJSVal #-}
instance FromJSVal DeviceProximityEventInit where
fromJSVal v = fmap DeviceProximityEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DeviceProximityEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DeviceProximityEventInit where
makeObject = makeObject . unDeviceProximityEventInit
instance IsEventInit DeviceProximityEventInit
instance IsGObject DeviceProximityEventInit where
typeGType _ = gTypeDeviceProximityEventInit
{-# INLINE typeGType #-}
noDeviceProximityEventInit :: Maybe DeviceProximityEventInit
noDeviceProximityEventInit = Nothing
{-# INLINE noDeviceProximityEventInit #-}
gTypeDeviceProximityEventInit :: JSM GType
gTypeDeviceProximityEventInit = GType . Object <$> jsg "DeviceProximityEventInit"
newtype Document = Document { unDocument :: JSVal }
instance PToJSVal Document where
pToJSVal = unDocument
{-# INLINE pToJSVal #-}
instance PFromJSVal Document where
pFromJSVal = Document
{-# INLINE pFromJSVal #-}
instance ToJSVal Document where
toJSVal = return . unDocument
{-# INLINE toJSVal #-}
instance FromJSVal Document where
fromJSVal v = fmap Document <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Document
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Document where
makeObject = makeObject . unDocument
class (IsNode o, IsEventTarget o, IsGlobalEventHandlers o, IsDocumentOrShadowRoot o, IsNonElementParentNode o, IsParentNode o, IsDocumentAndElementEventHandlers o, IsGObject o) => IsDocument o
toDocument :: IsDocument o => o -> Document
toDocument = Document . coerce
instance IsDocument Document
instance IsNode Document
instance IsEventTarget Document
instance IsGlobalEventHandlers Document
instance IsDocumentOrShadowRoot Document
instance IsNonElementParentNode Document
instance IsParentNode Document
instance IsDocumentAndElementEventHandlers Document
instance IsGObject Document where
typeGType _ = gTypeDocument
{-# INLINE typeGType #-}
noDocument :: Maybe Document
noDocument = Nothing
{-# INLINE noDocument #-}
gTypeDocument :: JSM GType
gTypeDocument = GType . Object <$> jsg "Document"
newtype DocumentAndElementEventHandlers = DocumentAndElementEventHandlers { unDocumentAndElementEventHandlers :: JSVal }
instance PToJSVal DocumentAndElementEventHandlers where
pToJSVal = unDocumentAndElementEventHandlers
{-# INLINE pToJSVal #-}
instance PFromJSVal DocumentAndElementEventHandlers where
pFromJSVal = DocumentAndElementEventHandlers
{-# INLINE pFromJSVal #-}
instance ToJSVal DocumentAndElementEventHandlers where
toJSVal = return . unDocumentAndElementEventHandlers
{-# INLINE toJSVal #-}
instance FromJSVal DocumentAndElementEventHandlers where
fromJSVal v = fmap DocumentAndElementEventHandlers <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DocumentAndElementEventHandlers
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DocumentAndElementEventHandlers where
makeObject = makeObject . unDocumentAndElementEventHandlers
class (IsGObject o) => IsDocumentAndElementEventHandlers o
toDocumentAndElementEventHandlers :: IsDocumentAndElementEventHandlers o => o -> DocumentAndElementEventHandlers
toDocumentAndElementEventHandlers = DocumentAndElementEventHandlers . coerce
instance IsDocumentAndElementEventHandlers DocumentAndElementEventHandlers
instance IsGObject DocumentAndElementEventHandlers where
typeGType _ = gTypeDocumentAndElementEventHandlers
{-# INLINE typeGType #-}
noDocumentAndElementEventHandlers :: Maybe DocumentAndElementEventHandlers
noDocumentAndElementEventHandlers = Nothing
{-# INLINE noDocumentAndElementEventHandlers #-}
gTypeDocumentAndElementEventHandlers :: JSM GType
gTypeDocumentAndElementEventHandlers = GType . Object <$> jsg "DocumentAndElementEventHandlers"
newtype DocumentFragment = DocumentFragment { unDocumentFragment :: JSVal }
instance PToJSVal DocumentFragment where
pToJSVal = unDocumentFragment
{-# INLINE pToJSVal #-}
instance PFromJSVal DocumentFragment where
pFromJSVal = DocumentFragment
{-# INLINE pFromJSVal #-}
instance ToJSVal DocumentFragment where
toJSVal = return . unDocumentFragment
{-# INLINE toJSVal #-}
instance FromJSVal DocumentFragment where
fromJSVal v = fmap DocumentFragment <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DocumentFragment
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DocumentFragment where
makeObject = makeObject . unDocumentFragment
class (IsNode o, IsEventTarget o, IsNonElementParentNode o, IsParentNode o, IsGObject o) => IsDocumentFragment o
toDocumentFragment :: IsDocumentFragment o => o -> DocumentFragment
toDocumentFragment = DocumentFragment . coerce
instance IsDocumentFragment DocumentFragment
instance IsNode DocumentFragment
instance IsEventTarget DocumentFragment
instance IsNonElementParentNode DocumentFragment
instance IsParentNode DocumentFragment
instance IsGObject DocumentFragment where
typeGType _ = gTypeDocumentFragment
{-# INLINE typeGType #-}
noDocumentFragment :: Maybe DocumentFragment
noDocumentFragment = Nothing
{-# INLINE noDocumentFragment #-}
gTypeDocumentFragment :: JSM GType
gTypeDocumentFragment = GType . Object <$> jsg "DocumentFragment"
newtype DocumentOrShadowRoot = DocumentOrShadowRoot { unDocumentOrShadowRoot :: JSVal }
instance PToJSVal DocumentOrShadowRoot where
pToJSVal = unDocumentOrShadowRoot
{-# INLINE pToJSVal #-}
instance PFromJSVal DocumentOrShadowRoot where
pFromJSVal = DocumentOrShadowRoot
{-# INLINE pFromJSVal #-}
instance ToJSVal DocumentOrShadowRoot where
toJSVal = return . unDocumentOrShadowRoot
{-# INLINE toJSVal #-}
instance FromJSVal DocumentOrShadowRoot where
fromJSVal v = fmap DocumentOrShadowRoot <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DocumentOrShadowRoot
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DocumentOrShadowRoot where
makeObject = makeObject . unDocumentOrShadowRoot
class (IsGObject o) => IsDocumentOrShadowRoot o
toDocumentOrShadowRoot :: IsDocumentOrShadowRoot o => o -> DocumentOrShadowRoot
toDocumentOrShadowRoot = DocumentOrShadowRoot . coerce
instance IsDocumentOrShadowRoot DocumentOrShadowRoot
instance IsGObject DocumentOrShadowRoot where
typeGType _ = gTypeDocumentOrShadowRoot
{-# INLINE typeGType #-}
noDocumentOrShadowRoot :: Maybe DocumentOrShadowRoot
noDocumentOrShadowRoot = Nothing
{-# INLINE noDocumentOrShadowRoot #-}
gTypeDocumentOrShadowRoot :: JSM GType
gTypeDocumentOrShadowRoot = GType . Object <$> jsg "DocumentOrShadowRoot"
newtype DocumentTimeline = DocumentTimeline { unDocumentTimeline :: JSVal }
instance PToJSVal DocumentTimeline where
pToJSVal = unDocumentTimeline
{-# INLINE pToJSVal #-}
instance PFromJSVal DocumentTimeline where
pFromJSVal = DocumentTimeline
{-# INLINE pFromJSVal #-}
instance ToJSVal DocumentTimeline where
toJSVal = return . unDocumentTimeline
{-# INLINE toJSVal #-}
instance FromJSVal DocumentTimeline where
fromJSVal v = fmap DocumentTimeline <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DocumentTimeline
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DocumentTimeline where
makeObject = makeObject . unDocumentTimeline
instance IsAnimationTimeline DocumentTimeline
instance IsGObject DocumentTimeline where
typeGType _ = gTypeDocumentTimeline
{-# INLINE typeGType #-}
noDocumentTimeline :: Maybe DocumentTimeline
noDocumentTimeline = Nothing
{-# INLINE noDocumentTimeline #-}
gTypeDocumentTimeline :: JSM GType
gTypeDocumentTimeline = GType . Object <$> jsg "DocumentTimeline"
newtype DocumentType = DocumentType { unDocumentType :: JSVal }
instance PToJSVal DocumentType where
pToJSVal = unDocumentType
{-# INLINE pToJSVal #-}
instance PFromJSVal DocumentType where
pFromJSVal = DocumentType
{-# INLINE pFromJSVal #-}
instance ToJSVal DocumentType where
toJSVal = return . unDocumentType
{-# INLINE toJSVal #-}
instance FromJSVal DocumentType where
fromJSVal v = fmap DocumentType <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DocumentType
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DocumentType where
makeObject = makeObject . unDocumentType
instance IsNode DocumentType
instance IsEventTarget DocumentType
instance IsChildNode DocumentType
instance IsGObject DocumentType where
typeGType _ = gTypeDocumentType
{-# INLINE typeGType #-}
noDocumentType :: Maybe DocumentType
noDocumentType = Nothing
{-# INLINE noDocumentType #-}
gTypeDocumentType :: JSM GType
gTypeDocumentType = GType . Object <$> jsg "DocumentType"
newtype DoubleRange = DoubleRange { unDoubleRange :: JSVal }
instance PToJSVal DoubleRange where
pToJSVal = unDoubleRange
{-# INLINE pToJSVal #-}
instance PFromJSVal DoubleRange where
pFromJSVal = DoubleRange
{-# INLINE pFromJSVal #-}
instance ToJSVal DoubleRange where
toJSVal = return . unDoubleRange
{-# INLINE toJSVal #-}
instance FromJSVal DoubleRange where
fromJSVal v = fmap DoubleRange <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DoubleRange
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DoubleRange where
makeObject = makeObject . unDoubleRange
class (IsGObject o) => IsDoubleRange o
toDoubleRange :: IsDoubleRange o => o -> DoubleRange
toDoubleRange = DoubleRange . coerce
instance IsDoubleRange DoubleRange
instance IsGObject DoubleRange where
typeGType _ = gTypeDoubleRange
{-# INLINE typeGType #-}
noDoubleRange :: Maybe DoubleRange
noDoubleRange = Nothing
{-# INLINE noDoubleRange #-}
gTypeDoubleRange :: JSM GType
gTypeDoubleRange = GType . Object <$> jsg "DoubleRange"
newtype DynamicsCompressorNode = DynamicsCompressorNode { unDynamicsCompressorNode :: JSVal }
instance PToJSVal DynamicsCompressorNode where
pToJSVal = unDynamicsCompressorNode
{-# INLINE pToJSVal #-}
instance PFromJSVal DynamicsCompressorNode where
pFromJSVal = DynamicsCompressorNode
{-# INLINE pFromJSVal #-}
instance ToJSVal DynamicsCompressorNode where
toJSVal = return . unDynamicsCompressorNode
{-# INLINE toJSVal #-}
instance FromJSVal DynamicsCompressorNode where
fromJSVal v = fmap DynamicsCompressorNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . DynamicsCompressorNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject DynamicsCompressorNode where
makeObject = makeObject . unDynamicsCompressorNode
instance IsAudioNode DynamicsCompressorNode
instance IsEventTarget DynamicsCompressorNode
instance IsGObject DynamicsCompressorNode where
typeGType _ = gTypeDynamicsCompressorNode
{-# INLINE typeGType #-}
noDynamicsCompressorNode :: Maybe DynamicsCompressorNode
noDynamicsCompressorNode = Nothing
{-# INLINE noDynamicsCompressorNode #-}
gTypeDynamicsCompressorNode :: JSM GType
gTypeDynamicsCompressorNode = GType . Object <$> jsg "DynamicsCompressorNode"
newtype EXTBlendMinMax = EXTBlendMinMax { unEXTBlendMinMax :: JSVal }
instance PToJSVal EXTBlendMinMax where
pToJSVal = unEXTBlendMinMax
{-# INLINE pToJSVal #-}
instance PFromJSVal EXTBlendMinMax where
pFromJSVal = EXTBlendMinMax
{-# INLINE pFromJSVal #-}
instance ToJSVal EXTBlendMinMax where
toJSVal = return . unEXTBlendMinMax
{-# INLINE toJSVal #-}
instance FromJSVal EXTBlendMinMax where
fromJSVal v = fmap EXTBlendMinMax <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EXTBlendMinMax
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EXTBlendMinMax where
makeObject = makeObject . unEXTBlendMinMax
instance IsGObject EXTBlendMinMax where
typeGType _ = gTypeEXTBlendMinMax
{-# INLINE typeGType #-}
noEXTBlendMinMax :: Maybe EXTBlendMinMax
noEXTBlendMinMax = Nothing
{-# INLINE noEXTBlendMinMax #-}
gTypeEXTBlendMinMax :: JSM GType
gTypeEXTBlendMinMax = GType . Object <$> jsg "EXTBlendMinMax"
newtype EXTFragDepth = EXTFragDepth { unEXTFragDepth :: JSVal }
instance PToJSVal EXTFragDepth where
pToJSVal = unEXTFragDepth
{-# INLINE pToJSVal #-}
instance PFromJSVal EXTFragDepth where
pFromJSVal = EXTFragDepth
{-# INLINE pFromJSVal #-}
instance ToJSVal EXTFragDepth where
toJSVal = return . unEXTFragDepth
{-# INLINE toJSVal #-}
instance FromJSVal EXTFragDepth where
fromJSVal v = fmap EXTFragDepth <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EXTFragDepth
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EXTFragDepth where
makeObject = makeObject . unEXTFragDepth
instance IsGObject EXTFragDepth where
typeGType _ = gTypeEXTFragDepth
{-# INLINE typeGType #-}
noEXTFragDepth :: Maybe EXTFragDepth
noEXTFragDepth = Nothing
{-# INLINE noEXTFragDepth #-}
gTypeEXTFragDepth :: JSM GType
gTypeEXTFragDepth = GType . Object <$> jsg "EXTFragDepth"
newtype EXTShaderTextureLOD = EXTShaderTextureLOD { unEXTShaderTextureLOD :: JSVal }
instance PToJSVal EXTShaderTextureLOD where
pToJSVal = unEXTShaderTextureLOD
{-# INLINE pToJSVal #-}
instance PFromJSVal EXTShaderTextureLOD where
pFromJSVal = EXTShaderTextureLOD
{-# INLINE pFromJSVal #-}
instance ToJSVal EXTShaderTextureLOD where
toJSVal = return . unEXTShaderTextureLOD
{-# INLINE toJSVal #-}
instance FromJSVal EXTShaderTextureLOD where
fromJSVal v = fmap EXTShaderTextureLOD <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EXTShaderTextureLOD
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EXTShaderTextureLOD where
makeObject = makeObject . unEXTShaderTextureLOD
instance IsGObject EXTShaderTextureLOD where
typeGType _ = gTypeEXTShaderTextureLOD
{-# INLINE typeGType #-}
noEXTShaderTextureLOD :: Maybe EXTShaderTextureLOD
noEXTShaderTextureLOD = Nothing
{-# INLINE noEXTShaderTextureLOD #-}
gTypeEXTShaderTextureLOD :: JSM GType
gTypeEXTShaderTextureLOD = GType . Object <$> jsg "EXTShaderTextureLOD"
newtype EXTTextureFilterAnisotropic = EXTTextureFilterAnisotropic { unEXTTextureFilterAnisotropic :: JSVal }
instance PToJSVal EXTTextureFilterAnisotropic where
pToJSVal = unEXTTextureFilterAnisotropic
{-# INLINE pToJSVal #-}
instance PFromJSVal EXTTextureFilterAnisotropic where
pFromJSVal = EXTTextureFilterAnisotropic
{-# INLINE pFromJSVal #-}
instance ToJSVal EXTTextureFilterAnisotropic where
toJSVal = return . unEXTTextureFilterAnisotropic
{-# INLINE toJSVal #-}
instance FromJSVal EXTTextureFilterAnisotropic where
fromJSVal v = fmap EXTTextureFilterAnisotropic <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EXTTextureFilterAnisotropic
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EXTTextureFilterAnisotropic where
makeObject = makeObject . unEXTTextureFilterAnisotropic
instance IsGObject EXTTextureFilterAnisotropic where
typeGType _ = gTypeEXTTextureFilterAnisotropic
{-# INLINE typeGType #-}
noEXTTextureFilterAnisotropic :: Maybe EXTTextureFilterAnisotropic
noEXTTextureFilterAnisotropic = Nothing
{-# INLINE noEXTTextureFilterAnisotropic #-}
gTypeEXTTextureFilterAnisotropic :: JSM GType
gTypeEXTTextureFilterAnisotropic = GType . Object <$> jsg "EXTTextureFilterAnisotropic"
newtype EXTsRGB = EXTsRGB { unEXTsRGB :: JSVal }
instance PToJSVal EXTsRGB where
pToJSVal = unEXTsRGB
{-# INLINE pToJSVal #-}
instance PFromJSVal EXTsRGB where
pFromJSVal = EXTsRGB
{-# INLINE pFromJSVal #-}
instance ToJSVal EXTsRGB where
toJSVal = return . unEXTsRGB
{-# INLINE toJSVal #-}
instance FromJSVal EXTsRGB where
fromJSVal v = fmap EXTsRGB <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EXTsRGB
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EXTsRGB where
makeObject = makeObject . unEXTsRGB
instance IsGObject EXTsRGB where
typeGType _ = gTypeEXTsRGB
{-# INLINE typeGType #-}
noEXTsRGB :: Maybe EXTsRGB
noEXTsRGB = Nothing
{-# INLINE noEXTsRGB #-}
gTypeEXTsRGB :: JSM GType
gTypeEXTsRGB = GType . Object <$> jsg "EXTsRGB"
newtype EcKeyParams = EcKeyParams { unEcKeyParams :: JSVal }
instance PToJSVal EcKeyParams where
pToJSVal = unEcKeyParams
{-# INLINE pToJSVal #-}
instance PFromJSVal EcKeyParams where
pFromJSVal = EcKeyParams
{-# INLINE pFromJSVal #-}
instance ToJSVal EcKeyParams where
toJSVal = return . unEcKeyParams
{-# INLINE toJSVal #-}
instance FromJSVal EcKeyParams where
fromJSVal v = fmap EcKeyParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EcKeyParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EcKeyParams where
makeObject = makeObject . unEcKeyParams
instance IsCryptoAlgorithmParameters EcKeyParams
instance IsGObject EcKeyParams where
typeGType _ = gTypeEcKeyParams
{-# INLINE typeGType #-}
noEcKeyParams :: Maybe EcKeyParams
noEcKeyParams = Nothing
{-# INLINE noEcKeyParams #-}
gTypeEcKeyParams :: JSM GType
gTypeEcKeyParams = GType . Object <$> jsg "EcKeyParams"
newtype EcdhKeyDeriveParams = EcdhKeyDeriveParams { unEcdhKeyDeriveParams :: JSVal }
instance PToJSVal EcdhKeyDeriveParams where
pToJSVal = unEcdhKeyDeriveParams
{-# INLINE pToJSVal #-}
instance PFromJSVal EcdhKeyDeriveParams where
pFromJSVal = EcdhKeyDeriveParams
{-# INLINE pFromJSVal #-}
instance ToJSVal EcdhKeyDeriveParams where
toJSVal = return . unEcdhKeyDeriveParams
{-# INLINE toJSVal #-}
instance FromJSVal EcdhKeyDeriveParams where
fromJSVal v = fmap EcdhKeyDeriveParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EcdhKeyDeriveParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EcdhKeyDeriveParams where
makeObject = makeObject . unEcdhKeyDeriveParams
instance IsCryptoAlgorithmParameters EcdhKeyDeriveParams
instance IsGObject EcdhKeyDeriveParams where
typeGType _ = gTypeEcdhKeyDeriveParams
{-# INLINE typeGType #-}
noEcdhKeyDeriveParams :: Maybe EcdhKeyDeriveParams
noEcdhKeyDeriveParams = Nothing
{-# INLINE noEcdhKeyDeriveParams #-}
gTypeEcdhKeyDeriveParams :: JSM GType
gTypeEcdhKeyDeriveParams = GType . Object <$> jsg "EcdhKeyDeriveParams"
newtype EcdsaParams = EcdsaParams { unEcdsaParams :: JSVal }
instance PToJSVal EcdsaParams where
pToJSVal = unEcdsaParams
{-# INLINE pToJSVal #-}
instance PFromJSVal EcdsaParams where
pFromJSVal = EcdsaParams
{-# INLINE pFromJSVal #-}
instance ToJSVal EcdsaParams where
toJSVal = return . unEcdsaParams
{-# INLINE toJSVal #-}
instance FromJSVal EcdsaParams where
fromJSVal v = fmap EcdsaParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EcdsaParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EcdsaParams where
makeObject = makeObject . unEcdsaParams
instance IsCryptoAlgorithmParameters EcdsaParams
instance IsGObject EcdsaParams where
typeGType _ = gTypeEcdsaParams
{-# INLINE typeGType #-}
noEcdsaParams :: Maybe EcdsaParams
noEcdsaParams = Nothing
{-# INLINE noEcdsaParams #-}
gTypeEcdsaParams :: JSM GType
gTypeEcdsaParams = GType . Object <$> jsg "EcdsaParams"
newtype Element = Element { unElement :: JSVal }
instance PToJSVal Element where
pToJSVal = unElement
{-# INLINE pToJSVal #-}
instance PFromJSVal Element where
pFromJSVal = Element
{-# INLINE pFromJSVal #-}
instance ToJSVal Element where
toJSVal = return . unElement
{-# INLINE toJSVal #-}
instance FromJSVal Element where
fromJSVal v = fmap Element <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Element
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Element where
makeObject = makeObject . unElement
class (IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGObject o) => IsElement o
toElement :: IsElement o => o -> Element
toElement = Element . coerce
instance IsElement Element
instance IsNode Element
instance IsEventTarget Element
instance IsSlotable Element
instance IsParentNode Element
instance IsNonDocumentTypeChildNode Element
instance IsDocumentAndElementEventHandlers Element
instance IsChildNode Element
instance IsAnimatable Element
instance IsGObject Element where
typeGType _ = gTypeElement
{-# INLINE typeGType #-}
noElement :: Maybe Element
noElement = Nothing
{-# INLINE noElement #-}
gTypeElement :: JSM GType
gTypeElement = GType . Object <$> jsg "Element"
newtype ElementCSSInlineStyle = ElementCSSInlineStyle { unElementCSSInlineStyle :: JSVal }
instance PToJSVal ElementCSSInlineStyle where
pToJSVal = unElementCSSInlineStyle
{-# INLINE pToJSVal #-}
instance PFromJSVal ElementCSSInlineStyle where
pFromJSVal = ElementCSSInlineStyle
{-# INLINE pFromJSVal #-}
instance ToJSVal ElementCSSInlineStyle where
toJSVal = return . unElementCSSInlineStyle
{-# INLINE toJSVal #-}
instance FromJSVal ElementCSSInlineStyle where
fromJSVal v = fmap ElementCSSInlineStyle <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ElementCSSInlineStyle
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ElementCSSInlineStyle where
makeObject = makeObject . unElementCSSInlineStyle
class (IsGObject o) => IsElementCSSInlineStyle o
toElementCSSInlineStyle :: IsElementCSSInlineStyle o => o -> ElementCSSInlineStyle
toElementCSSInlineStyle = ElementCSSInlineStyle . coerce
instance IsElementCSSInlineStyle ElementCSSInlineStyle
instance IsGObject ElementCSSInlineStyle where
typeGType _ = gTypeElementCSSInlineStyle
{-# INLINE typeGType #-}
noElementCSSInlineStyle :: Maybe ElementCSSInlineStyle
noElementCSSInlineStyle = Nothing
{-# INLINE noElementCSSInlineStyle #-}
gTypeElementCSSInlineStyle :: JSM GType
gTypeElementCSSInlineStyle = GType . Object <$> jsg "ElementCSSInlineStyle"
newtype ErrorEvent = ErrorEvent { unErrorEvent :: JSVal }
instance PToJSVal ErrorEvent where
pToJSVal = unErrorEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal ErrorEvent where
pFromJSVal = ErrorEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal ErrorEvent where
toJSVal = return . unErrorEvent
{-# INLINE toJSVal #-}
instance FromJSVal ErrorEvent where
fromJSVal v = fmap ErrorEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ErrorEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ErrorEvent where
makeObject = makeObject . unErrorEvent
instance IsEvent ErrorEvent
instance IsGObject ErrorEvent where
typeGType _ = gTypeErrorEvent
{-# INLINE typeGType #-}
noErrorEvent :: Maybe ErrorEvent
noErrorEvent = Nothing
{-# INLINE noErrorEvent #-}
gTypeErrorEvent :: JSM GType
gTypeErrorEvent = GType . Object <$> jsg "ErrorEvent"
newtype ErrorEventInit = ErrorEventInit { unErrorEventInit :: JSVal }
instance PToJSVal ErrorEventInit where
pToJSVal = unErrorEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal ErrorEventInit where
pFromJSVal = ErrorEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal ErrorEventInit where
toJSVal = return . unErrorEventInit
{-# INLINE toJSVal #-}
instance FromJSVal ErrorEventInit where
fromJSVal v = fmap ErrorEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ErrorEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ErrorEventInit where
makeObject = makeObject . unErrorEventInit
instance IsEventInit ErrorEventInit
instance IsGObject ErrorEventInit where
typeGType _ = gTypeErrorEventInit
{-# INLINE typeGType #-}
noErrorEventInit :: Maybe ErrorEventInit
noErrorEventInit = Nothing
{-# INLINE noErrorEventInit #-}
gTypeErrorEventInit :: JSM GType
gTypeErrorEventInit = GType . Object <$> jsg "ErrorEventInit"
newtype Event = Event { unEvent :: JSVal }
instance PToJSVal Event where
pToJSVal = unEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal Event where
pFromJSVal = Event
{-# INLINE pFromJSVal #-}
instance ToJSVal Event where
toJSVal = return . unEvent
{-# INLINE toJSVal #-}
instance FromJSVal Event where
fromJSVal v = fmap Event <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Event
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Event where
makeObject = makeObject . unEvent
class (IsGObject o) => IsEvent o
toEvent :: IsEvent o => o -> Event
toEvent = Event . coerce
instance IsEvent Event
instance IsGObject Event where
typeGType _ = gTypeEvent
{-# INLINE typeGType #-}
noEvent :: Maybe Event
noEvent = Nothing
{-# INLINE noEvent #-}
gTypeEvent :: JSM GType
gTypeEvent = GType . Object <$> jsg "Event"
newtype EventInit = EventInit { unEventInit :: JSVal }
instance PToJSVal EventInit where
pToJSVal = unEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal EventInit where
pFromJSVal = EventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal EventInit where
toJSVal = return . unEventInit
{-# INLINE toJSVal #-}
instance FromJSVal EventInit where
fromJSVal v = fmap EventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EventInit where
makeObject = makeObject . unEventInit
class (IsGObject o) => IsEventInit o
toEventInit :: IsEventInit o => o -> EventInit
toEventInit = EventInit . coerce
instance IsEventInit EventInit
instance IsGObject EventInit where
typeGType _ = gTypeEventInit
{-# INLINE typeGType #-}
noEventInit :: Maybe EventInit
noEventInit = Nothing
{-# INLINE noEventInit #-}
gTypeEventInit :: JSM GType
gTypeEventInit = GType . Object <$> jsg "EventInit"
newtype EventListener = EventListener { unEventListener :: JSVal }
instance PToJSVal EventListener where
pToJSVal = unEventListener
{-# INLINE pToJSVal #-}
instance PFromJSVal EventListener where
pFromJSVal = EventListener
{-# INLINE pFromJSVal #-}
instance ToJSVal EventListener where
toJSVal = return . unEventListener
{-# INLINE toJSVal #-}
instance FromJSVal EventListener where
fromJSVal v = fmap EventListener <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EventListener
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EventListener where
makeObject = makeObject . unEventListener
instance IsGObject EventListener where
typeGType _ = gTypeEventListener
{-# INLINE typeGType #-}
noEventListener :: Maybe EventListener
noEventListener = Nothing
{-# INLINE noEventListener #-}
gTypeEventListener :: JSM GType
gTypeEventListener = GType . Object <$> jsg "EventListener"
newtype EventListenerOptions = EventListenerOptions { unEventListenerOptions :: JSVal }
instance PToJSVal EventListenerOptions where
pToJSVal = unEventListenerOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal EventListenerOptions where
pFromJSVal = EventListenerOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal EventListenerOptions where
toJSVal = return . unEventListenerOptions
{-# INLINE toJSVal #-}
instance FromJSVal EventListenerOptions where
fromJSVal v = fmap EventListenerOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EventListenerOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EventListenerOptions where
makeObject = makeObject . unEventListenerOptions
class (IsGObject o) => IsEventListenerOptions o
toEventListenerOptions :: IsEventListenerOptions o => o -> EventListenerOptions
toEventListenerOptions = EventListenerOptions . coerce
instance IsEventListenerOptions EventListenerOptions
instance IsGObject EventListenerOptions where
typeGType _ = gTypeEventListenerOptions
{-# INLINE typeGType #-}
noEventListenerOptions :: Maybe EventListenerOptions
noEventListenerOptions = Nothing
{-# INLINE noEventListenerOptions #-}
gTypeEventListenerOptions :: JSM GType
gTypeEventListenerOptions = GType . Object <$> jsg "EventListenerOptions"
newtype EventModifierInit = EventModifierInit { unEventModifierInit :: JSVal }
instance PToJSVal EventModifierInit where
pToJSVal = unEventModifierInit
{-# INLINE pToJSVal #-}
instance PFromJSVal EventModifierInit where
pFromJSVal = EventModifierInit
{-# INLINE pFromJSVal #-}
instance ToJSVal EventModifierInit where
toJSVal = return . unEventModifierInit
{-# INLINE toJSVal #-}
instance FromJSVal EventModifierInit where
fromJSVal v = fmap EventModifierInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EventModifierInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EventModifierInit where
makeObject = makeObject . unEventModifierInit
class (IsUIEventInit o, IsEventInit o, IsGObject o) => IsEventModifierInit o
toEventModifierInit :: IsEventModifierInit o => o -> EventModifierInit
toEventModifierInit = EventModifierInit . coerce
instance IsEventModifierInit EventModifierInit
instance IsUIEventInit EventModifierInit
instance IsEventInit EventModifierInit
instance IsGObject EventModifierInit where
typeGType _ = gTypeEventModifierInit
{-# INLINE typeGType #-}
noEventModifierInit :: Maybe EventModifierInit
noEventModifierInit = Nothing
{-# INLINE noEventModifierInit #-}
gTypeEventModifierInit :: JSM GType
gTypeEventModifierInit = GType . Object <$> jsg "EventModifierInit"
newtype EventSource = EventSource { unEventSource :: JSVal }
instance PToJSVal EventSource where
pToJSVal = unEventSource
{-# INLINE pToJSVal #-}
instance PFromJSVal EventSource where
pFromJSVal = EventSource
{-# INLINE pFromJSVal #-}
instance ToJSVal EventSource where
toJSVal = return . unEventSource
{-# INLINE toJSVal #-}
instance FromJSVal EventSource where
fromJSVal v = fmap EventSource <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EventSource
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EventSource where
makeObject = makeObject . unEventSource
instance IsEventTarget EventSource
instance IsGObject EventSource where
typeGType _ = gTypeEventSource
{-# INLINE typeGType #-}
noEventSource :: Maybe EventSource
noEventSource = Nothing
{-# INLINE noEventSource #-}
gTypeEventSource :: JSM GType
gTypeEventSource = GType . Object <$> jsg "EventSource"
newtype EventSourceInit = EventSourceInit { unEventSourceInit :: JSVal }
instance PToJSVal EventSourceInit where
pToJSVal = unEventSourceInit
{-# INLINE pToJSVal #-}
instance PFromJSVal EventSourceInit where
pFromJSVal = EventSourceInit
{-# INLINE pFromJSVal #-}
instance ToJSVal EventSourceInit where
toJSVal = return . unEventSourceInit
{-# INLINE toJSVal #-}
instance FromJSVal EventSourceInit where
fromJSVal v = fmap EventSourceInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EventSourceInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EventSourceInit where
makeObject = makeObject . unEventSourceInit
instance IsGObject EventSourceInit where
typeGType _ = gTypeEventSourceInit
{-# INLINE typeGType #-}
noEventSourceInit :: Maybe EventSourceInit
noEventSourceInit = Nothing
{-# INLINE noEventSourceInit #-}
gTypeEventSourceInit :: JSM GType
gTypeEventSourceInit = GType . Object <$> jsg "EventSourceInit"
newtype EventTarget = EventTarget { unEventTarget :: JSVal }
instance PToJSVal EventTarget where
pToJSVal = unEventTarget
{-# INLINE pToJSVal #-}
instance PFromJSVal EventTarget where
pFromJSVal = EventTarget
{-# INLINE pFromJSVal #-}
instance ToJSVal EventTarget where
toJSVal = return . unEventTarget
{-# INLINE toJSVal #-}
instance FromJSVal EventTarget where
fromJSVal v = fmap EventTarget <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . EventTarget
{-# INLINE fromJSValUnchecked #-}
instance MakeObject EventTarget where
makeObject = makeObject . unEventTarget
class (IsGObject o) => IsEventTarget o
toEventTarget :: IsEventTarget o => o -> EventTarget
toEventTarget = EventTarget . coerce
instance IsEventTarget EventTarget
instance IsGObject EventTarget where
typeGType _ = gTypeEventTarget
{-# INLINE typeGType #-}
noEventTarget :: Maybe EventTarget
noEventTarget = Nothing
{-# INLINE noEventTarget #-}
gTypeEventTarget :: JSM GType
gTypeEventTarget = GType . Object <$> jsg "EventTarget"
newtype File = File { unFile :: JSVal }
instance PToJSVal File where
pToJSVal = unFile
{-# INLINE pToJSVal #-}
instance PFromJSVal File where
pFromJSVal = File
{-# INLINE pFromJSVal #-}
instance ToJSVal File where
toJSVal = return . unFile
{-# INLINE toJSVal #-}
instance FromJSVal File where
fromJSVal v = fmap File <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . File
{-# INLINE fromJSValUnchecked #-}
instance MakeObject File where
makeObject = makeObject . unFile
instance IsBlob File
instance IsGObject File where
typeGType _ = gTypeFile
{-# INLINE typeGType #-}
noFile :: Maybe File
noFile = Nothing
{-# INLINE noFile #-}
gTypeFile :: JSM GType
gTypeFile = GType . Object <$> jsg "File"
newtype FileError = FileError { unFileError :: JSVal }
instance PToJSVal FileError where
pToJSVal = unFileError
{-# INLINE pToJSVal #-}
instance PFromJSVal FileError where
pFromJSVal = FileError
{-# INLINE pFromJSVal #-}
instance ToJSVal FileError where
toJSVal = return . unFileError
{-# INLINE toJSVal #-}
instance FromJSVal FileError where
fromJSVal v = fmap FileError <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FileError
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FileError where
makeObject = makeObject . unFileError
instance IsGObject FileError where
typeGType _ = gTypeFileError
{-# INLINE typeGType #-}
noFileError :: Maybe FileError
noFileError = Nothing
{-# INLINE noFileError #-}
gTypeFileError :: JSM GType
gTypeFileError = GType . Object <$> jsg "FileError"
newtype FileException = FileException { unFileException :: JSVal }
instance PToJSVal FileException where
pToJSVal = unFileException
{-# INLINE pToJSVal #-}
instance PFromJSVal FileException where
pFromJSVal = FileException
{-# INLINE pFromJSVal #-}
instance ToJSVal FileException where
toJSVal = return . unFileException
{-# INLINE toJSVal #-}
instance FromJSVal FileException where
fromJSVal v = fmap FileException <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FileException
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FileException where
makeObject = makeObject . unFileException
instance IsGObject FileException where
typeGType _ = gTypeFileException
{-# INLINE typeGType #-}
noFileException :: Maybe FileException
noFileException = Nothing
{-# INLINE noFileException #-}
gTypeFileException :: JSM GType
gTypeFileException = GType . Object <$> jsg "FileException"
newtype FileList = FileList { unFileList :: JSVal }
instance PToJSVal FileList where
pToJSVal = unFileList
{-# INLINE pToJSVal #-}
instance PFromJSVal FileList where
pFromJSVal = FileList
{-# INLINE pFromJSVal #-}
instance ToJSVal FileList where
toJSVal = return . unFileList
{-# INLINE toJSVal #-}
instance FromJSVal FileList where
fromJSVal v = fmap FileList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FileList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FileList where
makeObject = makeObject . unFileList
instance IsGObject FileList where
typeGType _ = gTypeFileList
{-# INLINE typeGType #-}
noFileList :: Maybe FileList
noFileList = Nothing
{-# INLINE noFileList #-}
gTypeFileList :: JSM GType
gTypeFileList = GType . Object <$> jsg "FileList"
newtype FilePropertyBag = FilePropertyBag { unFilePropertyBag :: JSVal }
instance PToJSVal FilePropertyBag where
pToJSVal = unFilePropertyBag
{-# INLINE pToJSVal #-}
instance PFromJSVal FilePropertyBag where
pFromJSVal = FilePropertyBag
{-# INLINE pFromJSVal #-}
instance ToJSVal FilePropertyBag where
toJSVal = return . unFilePropertyBag
{-# INLINE toJSVal #-}
instance FromJSVal FilePropertyBag where
fromJSVal v = fmap FilePropertyBag <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FilePropertyBag
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FilePropertyBag where
makeObject = makeObject . unFilePropertyBag
instance IsBlobPropertyBag FilePropertyBag
instance IsGObject FilePropertyBag where
typeGType _ = gTypeFilePropertyBag
{-# INLINE typeGType #-}
noFilePropertyBag :: Maybe FilePropertyBag
noFilePropertyBag = Nothing
{-# INLINE noFilePropertyBag #-}
gTypeFilePropertyBag :: JSM GType
gTypeFilePropertyBag = GType . Object <$> jsg "FilePropertyBag"
newtype FileReader = FileReader { unFileReader :: JSVal }
instance PToJSVal FileReader where
pToJSVal = unFileReader
{-# INLINE pToJSVal #-}
instance PFromJSVal FileReader where
pFromJSVal = FileReader
{-# INLINE pFromJSVal #-}
instance ToJSVal FileReader where
toJSVal = return . unFileReader
{-# INLINE toJSVal #-}
instance FromJSVal FileReader where
fromJSVal v = fmap FileReader <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FileReader
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FileReader where
makeObject = makeObject . unFileReader
instance IsEventTarget FileReader
instance IsGObject FileReader where
typeGType _ = gTypeFileReader
{-# INLINE typeGType #-}
noFileReader :: Maybe FileReader
noFileReader = Nothing
{-# INLINE noFileReader #-}
gTypeFileReader :: JSM GType
gTypeFileReader = GType . Object <$> jsg "FileReader"
newtype FileReaderSync = FileReaderSync { unFileReaderSync :: JSVal }
instance PToJSVal FileReaderSync where
pToJSVal = unFileReaderSync
{-# INLINE pToJSVal #-}
instance PFromJSVal FileReaderSync where
pFromJSVal = FileReaderSync
{-# INLINE pFromJSVal #-}
instance ToJSVal FileReaderSync where
toJSVal = return . unFileReaderSync
{-# INLINE toJSVal #-}
instance FromJSVal FileReaderSync where
fromJSVal v = fmap FileReaderSync <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FileReaderSync
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FileReaderSync where
makeObject = makeObject . unFileReaderSync
instance IsGObject FileReaderSync where
typeGType _ = gTypeFileReaderSync
{-# INLINE typeGType #-}
noFileReaderSync :: Maybe FileReaderSync
noFileReaderSync = Nothing
{-# INLINE noFileReaderSync #-}
gTypeFileReaderSync :: JSM GType
gTypeFileReaderSync = GType . Object <$> jsg "FileReaderSync"
newtype FocusEvent = FocusEvent { unFocusEvent :: JSVal }
instance PToJSVal FocusEvent where
pToJSVal = unFocusEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal FocusEvent where
pFromJSVal = FocusEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal FocusEvent where
toJSVal = return . unFocusEvent
{-# INLINE toJSVal #-}
instance FromJSVal FocusEvent where
fromJSVal v = fmap FocusEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FocusEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FocusEvent where
makeObject = makeObject . unFocusEvent
instance IsUIEvent FocusEvent
instance IsEvent FocusEvent
instance IsGObject FocusEvent where
typeGType _ = gTypeFocusEvent
{-# INLINE typeGType #-}
noFocusEvent :: Maybe FocusEvent
noFocusEvent = Nothing
{-# INLINE noFocusEvent #-}
gTypeFocusEvent :: JSM GType
gTypeFocusEvent = GType . Object <$> jsg "FocusEvent"
newtype FocusEventInit = FocusEventInit { unFocusEventInit :: JSVal }
instance PToJSVal FocusEventInit where
pToJSVal = unFocusEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal FocusEventInit where
pFromJSVal = FocusEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal FocusEventInit where
toJSVal = return . unFocusEventInit
{-# INLINE toJSVal #-}
instance FromJSVal FocusEventInit where
fromJSVal v = fmap FocusEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FocusEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FocusEventInit where
makeObject = makeObject . unFocusEventInit
instance IsUIEventInit FocusEventInit
instance IsEventInit FocusEventInit
instance IsGObject FocusEventInit where
typeGType _ = gTypeFocusEventInit
{-# INLINE typeGType #-}
noFocusEventInit :: Maybe FocusEventInit
noFocusEventInit = Nothing
{-# INLINE noFocusEventInit #-}
gTypeFocusEventInit :: JSM GType
gTypeFocusEventInit = GType . Object <$> jsg "FocusEventInit"
newtype FontFace = FontFace { unFontFace :: JSVal }
instance PToJSVal FontFace where
pToJSVal = unFontFace
{-# INLINE pToJSVal #-}
instance PFromJSVal FontFace where
pFromJSVal = FontFace
{-# INLINE pFromJSVal #-}
instance ToJSVal FontFace where
toJSVal = return . unFontFace
{-# INLINE toJSVal #-}
instance FromJSVal FontFace where
fromJSVal v = fmap FontFace <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FontFace
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FontFace where
makeObject = makeObject . unFontFace
instance IsGObject FontFace where
typeGType _ = gTypeFontFace
{-# INLINE typeGType #-}
noFontFace :: Maybe FontFace
noFontFace = Nothing
{-# INLINE noFontFace #-}
gTypeFontFace :: JSM GType
gTypeFontFace = GType . Object <$> jsg "FontFace"
newtype FontFaceDescriptors = FontFaceDescriptors { unFontFaceDescriptors :: JSVal }
instance PToJSVal FontFaceDescriptors where
pToJSVal = unFontFaceDescriptors
{-# INLINE pToJSVal #-}
instance PFromJSVal FontFaceDescriptors where
pFromJSVal = FontFaceDescriptors
{-# INLINE pFromJSVal #-}
instance ToJSVal FontFaceDescriptors where
toJSVal = return . unFontFaceDescriptors
{-# INLINE toJSVal #-}
instance FromJSVal FontFaceDescriptors where
fromJSVal v = fmap FontFaceDescriptors <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FontFaceDescriptors
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FontFaceDescriptors where
makeObject = makeObject . unFontFaceDescriptors
instance IsGObject FontFaceDescriptors where
typeGType _ = gTypeFontFaceDescriptors
{-# INLINE typeGType #-}
noFontFaceDescriptors :: Maybe FontFaceDescriptors
noFontFaceDescriptors = Nothing
{-# INLINE noFontFaceDescriptors #-}
gTypeFontFaceDescriptors :: JSM GType
gTypeFontFaceDescriptors = GType . Object <$> jsg "FontFaceDescriptors"
newtype FontFaceSet = FontFaceSet { unFontFaceSet :: JSVal }
instance PToJSVal FontFaceSet where
pToJSVal = unFontFaceSet
{-# INLINE pToJSVal #-}
instance PFromJSVal FontFaceSet where
pFromJSVal = FontFaceSet
{-# INLINE pFromJSVal #-}
instance ToJSVal FontFaceSet where
toJSVal = return . unFontFaceSet
{-# INLINE toJSVal #-}
instance FromJSVal FontFaceSet where
fromJSVal v = fmap FontFaceSet <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FontFaceSet
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FontFaceSet where
makeObject = makeObject . unFontFaceSet
instance IsEventTarget FontFaceSet
instance IsGObject FontFaceSet where
typeGType _ = gTypeFontFaceSet
{-# INLINE typeGType #-}
noFontFaceSet :: Maybe FontFaceSet
noFontFaceSet = Nothing
{-# INLINE noFontFaceSet #-}
gTypeFontFaceSet :: JSM GType
gTypeFontFaceSet = GType . Object <$> jsg "FontFaceSet"
newtype FormData = FormData { unFormData :: JSVal }
instance PToJSVal FormData where
pToJSVal = unFormData
{-# INLINE pToJSVal #-}
instance PFromJSVal FormData where
pFromJSVal = FormData
{-# INLINE pFromJSVal #-}
instance ToJSVal FormData where
toJSVal = return . unFormData
{-# INLINE toJSVal #-}
instance FromJSVal FormData where
fromJSVal v = fmap FormData <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . FormData
{-# INLINE fromJSValUnchecked #-}
instance MakeObject FormData where
makeObject = makeObject . unFormData
instance IsGObject FormData where
typeGType _ = gTypeFormData
{-# INLINE typeGType #-}
noFormData :: Maybe FormData
noFormData = Nothing
{-# INLINE noFormData #-}
gTypeFormData :: JSM GType
gTypeFormData = GType . Object <$> jsg "FormData"
newtype GainNode = GainNode { unGainNode :: JSVal }
instance PToJSVal GainNode where
pToJSVal = unGainNode
{-# INLINE pToJSVal #-}
instance PFromJSVal GainNode where
pFromJSVal = GainNode
{-# INLINE pFromJSVal #-}
instance ToJSVal GainNode where
toJSVal = return . unGainNode
{-# INLINE toJSVal #-}
instance FromJSVal GainNode where
fromJSVal v = fmap GainNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . GainNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject GainNode where
makeObject = makeObject . unGainNode
instance IsAudioNode GainNode
instance IsEventTarget GainNode
instance IsGObject GainNode where
typeGType _ = gTypeGainNode
{-# INLINE typeGType #-}
noGainNode :: Maybe GainNode
noGainNode = Nothing
{-# INLINE noGainNode #-}
gTypeGainNode :: JSM GType
gTypeGainNode = GType . Object <$> jsg "GainNode"
newtype Gamepad = Gamepad { unGamepad :: JSVal }
instance PToJSVal Gamepad where
pToJSVal = unGamepad
{-# INLINE pToJSVal #-}
instance PFromJSVal Gamepad where
pFromJSVal = Gamepad
{-# INLINE pFromJSVal #-}
instance ToJSVal Gamepad where
toJSVal = return . unGamepad
{-# INLINE toJSVal #-}
instance FromJSVal Gamepad where
fromJSVal v = fmap Gamepad <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Gamepad
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Gamepad where
makeObject = makeObject . unGamepad
instance IsGObject Gamepad where
typeGType _ = gTypeGamepad
{-# INLINE typeGType #-}
noGamepad :: Maybe Gamepad
noGamepad = Nothing
{-# INLINE noGamepad #-}
gTypeGamepad :: JSM GType
gTypeGamepad = GType . Object <$> jsg "Gamepad"
newtype GamepadButton = GamepadButton { unGamepadButton :: JSVal }
instance PToJSVal GamepadButton where
pToJSVal = unGamepadButton
{-# INLINE pToJSVal #-}
instance PFromJSVal GamepadButton where
pFromJSVal = GamepadButton
{-# INLINE pFromJSVal #-}
instance ToJSVal GamepadButton where
toJSVal = return . unGamepadButton
{-# INLINE toJSVal #-}
instance FromJSVal GamepadButton where
fromJSVal v = fmap GamepadButton <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . GamepadButton
{-# INLINE fromJSValUnchecked #-}
instance MakeObject GamepadButton where
makeObject = makeObject . unGamepadButton
instance IsGObject GamepadButton where
typeGType _ = gTypeGamepadButton
{-# INLINE typeGType #-}
noGamepadButton :: Maybe GamepadButton
noGamepadButton = Nothing
{-# INLINE noGamepadButton #-}
gTypeGamepadButton :: JSM GType
gTypeGamepadButton = GType . Object <$> jsg "GamepadButton"
newtype GamepadEvent = GamepadEvent { unGamepadEvent :: JSVal }
instance PToJSVal GamepadEvent where
pToJSVal = unGamepadEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal GamepadEvent where
pFromJSVal = GamepadEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal GamepadEvent where
toJSVal = return . unGamepadEvent
{-# INLINE toJSVal #-}
instance FromJSVal GamepadEvent where
fromJSVal v = fmap GamepadEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . GamepadEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject GamepadEvent where
makeObject = makeObject . unGamepadEvent
instance IsEvent GamepadEvent
instance IsGObject GamepadEvent where
typeGType _ = gTypeGamepadEvent
{-# INLINE typeGType #-}
noGamepadEvent :: Maybe GamepadEvent
noGamepadEvent = Nothing
{-# INLINE noGamepadEvent #-}
gTypeGamepadEvent :: JSM GType
gTypeGamepadEvent = GType . Object <$> jsg "GamepadEvent"
newtype GamepadEventInit = GamepadEventInit { unGamepadEventInit :: JSVal }
instance PToJSVal GamepadEventInit where
pToJSVal = unGamepadEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal GamepadEventInit where
pFromJSVal = GamepadEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal GamepadEventInit where
toJSVal = return . unGamepadEventInit
{-# INLINE toJSVal #-}
instance FromJSVal GamepadEventInit where
fromJSVal v = fmap GamepadEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . GamepadEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject GamepadEventInit where
makeObject = makeObject . unGamepadEventInit
instance IsEventInit GamepadEventInit
instance IsGObject GamepadEventInit where
typeGType _ = gTypeGamepadEventInit
{-# INLINE typeGType #-}
noGamepadEventInit :: Maybe GamepadEventInit
noGamepadEventInit = Nothing
{-# INLINE noGamepadEventInit #-}
gTypeGamepadEventInit :: JSM GType
gTypeGamepadEventInit = GType . Object <$> jsg "GamepadEventInit"
newtype Geolocation = Geolocation { unGeolocation :: JSVal }
instance PToJSVal Geolocation where
pToJSVal = unGeolocation
{-# INLINE pToJSVal #-}
instance PFromJSVal Geolocation where
pFromJSVal = Geolocation
{-# INLINE pFromJSVal #-}
instance ToJSVal Geolocation where
toJSVal = return . unGeolocation
{-# INLINE toJSVal #-}
instance FromJSVal Geolocation where
fromJSVal v = fmap Geolocation <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Geolocation
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Geolocation where
makeObject = makeObject . unGeolocation
instance IsGObject Geolocation where
typeGType _ = gTypeGeolocation
{-# INLINE typeGType #-}
noGeolocation :: Maybe Geolocation
noGeolocation = Nothing
{-# INLINE noGeolocation #-}
gTypeGeolocation :: JSM GType
gTypeGeolocation = GType . Object <$> jsg "Geolocation"
newtype Geoposition = Geoposition { unGeoposition :: JSVal }
instance PToJSVal Geoposition where
pToJSVal = unGeoposition
{-# INLINE pToJSVal #-}
instance PFromJSVal Geoposition where
pFromJSVal = Geoposition
{-# INLINE pFromJSVal #-}
instance ToJSVal Geoposition where
toJSVal = return . unGeoposition
{-# INLINE toJSVal #-}
instance FromJSVal Geoposition where
fromJSVal v = fmap Geoposition <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Geoposition
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Geoposition where
makeObject = makeObject . unGeoposition
instance IsGObject Geoposition where
typeGType _ = gTypeGeoposition
{-# INLINE typeGType #-}
noGeoposition :: Maybe Geoposition
noGeoposition = Nothing
{-# INLINE noGeoposition #-}
gTypeGeoposition :: JSM GType
gTypeGeoposition = GType . Object <$> jsg "Geoposition"
newtype GetRootNodeOptions = GetRootNodeOptions { unGetRootNodeOptions :: JSVal }
instance PToJSVal GetRootNodeOptions where
pToJSVal = unGetRootNodeOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal GetRootNodeOptions where
pFromJSVal = GetRootNodeOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal GetRootNodeOptions where
toJSVal = return . unGetRootNodeOptions
{-# INLINE toJSVal #-}
instance FromJSVal GetRootNodeOptions where
fromJSVal v = fmap GetRootNodeOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . GetRootNodeOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject GetRootNodeOptions where
makeObject = makeObject . unGetRootNodeOptions
instance IsGObject GetRootNodeOptions where
typeGType _ = gTypeGetRootNodeOptions
{-# INLINE typeGType #-}
noGetRootNodeOptions :: Maybe GetRootNodeOptions
noGetRootNodeOptions = Nothing
{-# INLINE noGetRootNodeOptions #-}
gTypeGetRootNodeOptions :: JSM GType
gTypeGetRootNodeOptions = GType . Object <$> jsg "GetRootNodeOptions"
newtype GlobalCrypto = GlobalCrypto { unGlobalCrypto :: JSVal }
instance PToJSVal GlobalCrypto where
pToJSVal = unGlobalCrypto
{-# INLINE pToJSVal #-}
instance PFromJSVal GlobalCrypto where
pFromJSVal = GlobalCrypto
{-# INLINE pFromJSVal #-}
instance ToJSVal GlobalCrypto where
toJSVal = return . unGlobalCrypto
{-# INLINE toJSVal #-}
instance FromJSVal GlobalCrypto where
fromJSVal v = fmap GlobalCrypto <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . GlobalCrypto
{-# INLINE fromJSValUnchecked #-}
instance MakeObject GlobalCrypto where
makeObject = makeObject . unGlobalCrypto
class (IsGObject o) => IsGlobalCrypto o
toGlobalCrypto :: IsGlobalCrypto o => o -> GlobalCrypto
toGlobalCrypto = GlobalCrypto . coerce
instance IsGlobalCrypto GlobalCrypto
instance IsGObject GlobalCrypto where
typeGType _ = gTypeGlobalCrypto
{-# INLINE typeGType #-}
noGlobalCrypto :: Maybe GlobalCrypto
noGlobalCrypto = Nothing
{-# INLINE noGlobalCrypto #-}
gTypeGlobalCrypto :: JSM GType
gTypeGlobalCrypto = GType . Object <$> jsg "GlobalCrypto"
newtype GlobalEventHandlers = GlobalEventHandlers { unGlobalEventHandlers :: JSVal }
instance PToJSVal GlobalEventHandlers where
pToJSVal = unGlobalEventHandlers
{-# INLINE pToJSVal #-}
instance PFromJSVal GlobalEventHandlers where
pFromJSVal = GlobalEventHandlers
{-# INLINE pFromJSVal #-}
instance ToJSVal GlobalEventHandlers where
toJSVal = return . unGlobalEventHandlers
{-# INLINE toJSVal #-}
instance FromJSVal GlobalEventHandlers where
fromJSVal v = fmap GlobalEventHandlers <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . GlobalEventHandlers
{-# INLINE fromJSValUnchecked #-}
instance MakeObject GlobalEventHandlers where
makeObject = makeObject . unGlobalEventHandlers
class (IsGObject o) => IsGlobalEventHandlers o
toGlobalEventHandlers :: IsGlobalEventHandlers o => o -> GlobalEventHandlers
toGlobalEventHandlers = GlobalEventHandlers . coerce
instance IsGlobalEventHandlers GlobalEventHandlers
instance IsGObject GlobalEventHandlers where
typeGType _ = gTypeGlobalEventHandlers
{-# INLINE typeGType #-}
noGlobalEventHandlers :: Maybe GlobalEventHandlers
noGlobalEventHandlers = Nothing
{-# INLINE noGlobalEventHandlers #-}
gTypeGlobalEventHandlers :: JSM GType
gTypeGlobalEventHandlers = GType . Object <$> jsg "GlobalEventHandlers"
newtype GlobalPerformance = GlobalPerformance { unGlobalPerformance :: JSVal }
instance PToJSVal GlobalPerformance where
pToJSVal = unGlobalPerformance
{-# INLINE pToJSVal #-}
instance PFromJSVal GlobalPerformance where
pFromJSVal = GlobalPerformance
{-# INLINE pFromJSVal #-}
instance ToJSVal GlobalPerformance where
toJSVal = return . unGlobalPerformance
{-# INLINE toJSVal #-}
instance FromJSVal GlobalPerformance where
fromJSVal v = fmap GlobalPerformance <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . GlobalPerformance
{-# INLINE fromJSValUnchecked #-}
instance MakeObject GlobalPerformance where
makeObject = makeObject . unGlobalPerformance
class (IsGObject o) => IsGlobalPerformance o
toGlobalPerformance :: IsGlobalPerformance o => o -> GlobalPerformance
toGlobalPerformance = GlobalPerformance . coerce
instance IsGlobalPerformance GlobalPerformance
instance IsGObject GlobalPerformance where
typeGType _ = gTypeGlobalPerformance
{-# INLINE typeGType #-}
noGlobalPerformance :: Maybe GlobalPerformance
noGlobalPerformance = Nothing
{-# INLINE noGlobalPerformance #-}
gTypeGlobalPerformance :: JSM GType
gTypeGlobalPerformance = GType . Object <$> jsg "GlobalPerformance"
newtype HTMLAllCollection = HTMLAllCollection { unHTMLAllCollection :: JSVal }
instance PToJSVal HTMLAllCollection where
pToJSVal = unHTMLAllCollection
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLAllCollection where
pFromJSVal = HTMLAllCollection
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLAllCollection where
toJSVal = return . unHTMLAllCollection
{-# INLINE toJSVal #-}
instance FromJSVal HTMLAllCollection where
fromJSVal v = fmap HTMLAllCollection <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLAllCollection
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLAllCollection where
makeObject = makeObject . unHTMLAllCollection
instance IsGObject HTMLAllCollection where
typeGType _ = gTypeHTMLAllCollection
{-# INLINE typeGType #-}
noHTMLAllCollection :: Maybe HTMLAllCollection
noHTMLAllCollection = Nothing
{-# INLINE noHTMLAllCollection #-}
gTypeHTMLAllCollection :: JSM GType
gTypeHTMLAllCollection = GType . Object <$> jsg "HTMLAllCollection"
newtype HTMLAnchorElement = HTMLAnchorElement { unHTMLAnchorElement :: JSVal }
instance PToJSVal HTMLAnchorElement where
pToJSVal = unHTMLAnchorElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLAnchorElement where
pFromJSVal = HTMLAnchorElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLAnchorElement where
toJSVal = return . unHTMLAnchorElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLAnchorElement where
fromJSVal v = fmap HTMLAnchorElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLAnchorElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLAnchorElement where
makeObject = makeObject . unHTMLAnchorElement
instance IsHTMLElement HTMLAnchorElement
instance IsElement HTMLAnchorElement
instance IsNode HTMLAnchorElement
instance IsEventTarget HTMLAnchorElement
instance IsSlotable HTMLAnchorElement
instance IsParentNode HTMLAnchorElement
instance IsNonDocumentTypeChildNode HTMLAnchorElement
instance IsDocumentAndElementEventHandlers HTMLAnchorElement
instance IsChildNode HTMLAnchorElement
instance IsAnimatable HTMLAnchorElement
instance IsGlobalEventHandlers HTMLAnchorElement
instance IsElementCSSInlineStyle HTMLAnchorElement
instance IsHTMLHyperlinkElementUtils HTMLAnchorElement
instance IsGObject HTMLAnchorElement where
typeGType _ = gTypeHTMLAnchorElement
{-# INLINE typeGType #-}
noHTMLAnchorElement :: Maybe HTMLAnchorElement
noHTMLAnchorElement = Nothing
{-# INLINE noHTMLAnchorElement #-}
gTypeHTMLAnchorElement :: JSM GType
gTypeHTMLAnchorElement = GType . Object <$> jsg "HTMLAnchorElement"
newtype HTMLAppletElement = HTMLAppletElement { unHTMLAppletElement :: JSVal }
instance PToJSVal HTMLAppletElement where
pToJSVal = unHTMLAppletElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLAppletElement where
pFromJSVal = HTMLAppletElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLAppletElement where
toJSVal = return . unHTMLAppletElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLAppletElement where
fromJSVal v = fmap HTMLAppletElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLAppletElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLAppletElement where
makeObject = makeObject . unHTMLAppletElement
instance IsHTMLElement HTMLAppletElement
instance IsElement HTMLAppletElement
instance IsNode HTMLAppletElement
instance IsEventTarget HTMLAppletElement
instance IsSlotable HTMLAppletElement
instance IsParentNode HTMLAppletElement
instance IsNonDocumentTypeChildNode HTMLAppletElement
instance IsDocumentAndElementEventHandlers HTMLAppletElement
instance IsChildNode HTMLAppletElement
instance IsAnimatable HTMLAppletElement
instance IsGlobalEventHandlers HTMLAppletElement
instance IsElementCSSInlineStyle HTMLAppletElement
instance IsGObject HTMLAppletElement where
typeGType _ = gTypeHTMLAppletElement
{-# INLINE typeGType #-}
noHTMLAppletElement :: Maybe HTMLAppletElement
noHTMLAppletElement = Nothing
{-# INLINE noHTMLAppletElement #-}
gTypeHTMLAppletElement :: JSM GType
gTypeHTMLAppletElement = GType . Object <$> jsg "HTMLAppletElement"
newtype HTMLAreaElement = HTMLAreaElement { unHTMLAreaElement :: JSVal }
instance PToJSVal HTMLAreaElement where
pToJSVal = unHTMLAreaElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLAreaElement where
pFromJSVal = HTMLAreaElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLAreaElement where
toJSVal = return . unHTMLAreaElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLAreaElement where
fromJSVal v = fmap HTMLAreaElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLAreaElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLAreaElement where
makeObject = makeObject . unHTMLAreaElement
instance IsHTMLElement HTMLAreaElement
instance IsElement HTMLAreaElement
instance IsNode HTMLAreaElement
instance IsEventTarget HTMLAreaElement
instance IsSlotable HTMLAreaElement
instance IsParentNode HTMLAreaElement
instance IsNonDocumentTypeChildNode HTMLAreaElement
instance IsDocumentAndElementEventHandlers HTMLAreaElement
instance IsChildNode HTMLAreaElement
instance IsAnimatable HTMLAreaElement
instance IsGlobalEventHandlers HTMLAreaElement
instance IsElementCSSInlineStyle HTMLAreaElement
instance IsHTMLHyperlinkElementUtils HTMLAreaElement
instance IsGObject HTMLAreaElement where
typeGType _ = gTypeHTMLAreaElement
{-# INLINE typeGType #-}
noHTMLAreaElement :: Maybe HTMLAreaElement
noHTMLAreaElement = Nothing
{-# INLINE noHTMLAreaElement #-}
gTypeHTMLAreaElement :: JSM GType
gTypeHTMLAreaElement = GType . Object <$> jsg "HTMLAreaElement"
newtype HTMLAttachmentElement = HTMLAttachmentElement { unHTMLAttachmentElement :: JSVal }
instance PToJSVal HTMLAttachmentElement where
pToJSVal = unHTMLAttachmentElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLAttachmentElement where
pFromJSVal = HTMLAttachmentElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLAttachmentElement where
toJSVal = return . unHTMLAttachmentElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLAttachmentElement where
fromJSVal v = fmap HTMLAttachmentElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLAttachmentElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLAttachmentElement where
makeObject = makeObject . unHTMLAttachmentElement
instance IsHTMLElement HTMLAttachmentElement
instance IsElement HTMLAttachmentElement
instance IsNode HTMLAttachmentElement
instance IsEventTarget HTMLAttachmentElement
instance IsSlotable HTMLAttachmentElement
instance IsParentNode HTMLAttachmentElement
instance IsNonDocumentTypeChildNode HTMLAttachmentElement
instance IsDocumentAndElementEventHandlers HTMLAttachmentElement
instance IsChildNode HTMLAttachmentElement
instance IsAnimatable HTMLAttachmentElement
instance IsGlobalEventHandlers HTMLAttachmentElement
instance IsElementCSSInlineStyle HTMLAttachmentElement
instance IsGObject HTMLAttachmentElement where
typeGType _ = gTypeHTMLAttachmentElement
{-# INLINE typeGType #-}
noHTMLAttachmentElement :: Maybe HTMLAttachmentElement
noHTMLAttachmentElement = Nothing
{-# INLINE noHTMLAttachmentElement #-}
gTypeHTMLAttachmentElement :: JSM GType
gTypeHTMLAttachmentElement = GType . Object <$> jsg "HTMLAttachmentElement"
newtype HTMLAudioElement = HTMLAudioElement { unHTMLAudioElement :: JSVal }
instance PToJSVal HTMLAudioElement where
pToJSVal = unHTMLAudioElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLAudioElement where
pFromJSVal = HTMLAudioElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLAudioElement where
toJSVal = return . unHTMLAudioElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLAudioElement where
fromJSVal v = fmap HTMLAudioElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLAudioElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLAudioElement where
makeObject = makeObject . unHTMLAudioElement
instance IsHTMLMediaElement HTMLAudioElement
instance IsHTMLElement HTMLAudioElement
instance IsElement HTMLAudioElement
instance IsNode HTMLAudioElement
instance IsEventTarget HTMLAudioElement
instance IsSlotable HTMLAudioElement
instance IsParentNode HTMLAudioElement
instance IsNonDocumentTypeChildNode HTMLAudioElement
instance IsDocumentAndElementEventHandlers HTMLAudioElement
instance IsChildNode HTMLAudioElement
instance IsAnimatable HTMLAudioElement
instance IsGlobalEventHandlers HTMLAudioElement
instance IsElementCSSInlineStyle HTMLAudioElement
instance IsGObject HTMLAudioElement where
typeGType _ = gTypeHTMLAudioElement
{-# INLINE typeGType #-}
noHTMLAudioElement :: Maybe HTMLAudioElement
noHTMLAudioElement = Nothing
{-# INLINE noHTMLAudioElement #-}
gTypeHTMLAudioElement :: JSM GType
gTypeHTMLAudioElement = GType . Object <$> jsg "HTMLAudioElement"
newtype HTMLBRElement = HTMLBRElement { unHTMLBRElement :: JSVal }
instance PToJSVal HTMLBRElement where
pToJSVal = unHTMLBRElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLBRElement where
pFromJSVal = HTMLBRElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLBRElement where
toJSVal = return . unHTMLBRElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLBRElement where
fromJSVal v = fmap HTMLBRElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLBRElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLBRElement where
makeObject = makeObject . unHTMLBRElement
instance IsHTMLElement HTMLBRElement
instance IsElement HTMLBRElement
instance IsNode HTMLBRElement
instance IsEventTarget HTMLBRElement
instance IsSlotable HTMLBRElement
instance IsParentNode HTMLBRElement
instance IsNonDocumentTypeChildNode HTMLBRElement
instance IsDocumentAndElementEventHandlers HTMLBRElement
instance IsChildNode HTMLBRElement
instance IsAnimatable HTMLBRElement
instance IsGlobalEventHandlers HTMLBRElement
instance IsElementCSSInlineStyle HTMLBRElement
instance IsGObject HTMLBRElement where
typeGType _ = gTypeHTMLBRElement
{-# INLINE typeGType #-}
noHTMLBRElement :: Maybe HTMLBRElement
noHTMLBRElement = Nothing
{-# INLINE noHTMLBRElement #-}
gTypeHTMLBRElement :: JSM GType
gTypeHTMLBRElement = GType . Object <$> jsg "HTMLBRElement"
newtype HTMLBaseElement = HTMLBaseElement { unHTMLBaseElement :: JSVal }
instance PToJSVal HTMLBaseElement where
pToJSVal = unHTMLBaseElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLBaseElement where
pFromJSVal = HTMLBaseElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLBaseElement where
toJSVal = return . unHTMLBaseElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLBaseElement where
fromJSVal v = fmap HTMLBaseElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLBaseElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLBaseElement where
makeObject = makeObject . unHTMLBaseElement
instance IsHTMLElement HTMLBaseElement
instance IsElement HTMLBaseElement
instance IsNode HTMLBaseElement
instance IsEventTarget HTMLBaseElement
instance IsSlotable HTMLBaseElement
instance IsParentNode HTMLBaseElement
instance IsNonDocumentTypeChildNode HTMLBaseElement
instance IsDocumentAndElementEventHandlers HTMLBaseElement
instance IsChildNode HTMLBaseElement
instance IsAnimatable HTMLBaseElement
instance IsGlobalEventHandlers HTMLBaseElement
instance IsElementCSSInlineStyle HTMLBaseElement
instance IsGObject HTMLBaseElement where
typeGType _ = gTypeHTMLBaseElement
{-# INLINE typeGType #-}
noHTMLBaseElement :: Maybe HTMLBaseElement
noHTMLBaseElement = Nothing
{-# INLINE noHTMLBaseElement #-}
gTypeHTMLBaseElement :: JSM GType
gTypeHTMLBaseElement = GType . Object <$> jsg "HTMLBaseElement"
newtype HTMLBodyElement = HTMLBodyElement { unHTMLBodyElement :: JSVal }
instance PToJSVal HTMLBodyElement where
pToJSVal = unHTMLBodyElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLBodyElement where
pFromJSVal = HTMLBodyElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLBodyElement where
toJSVal = return . unHTMLBodyElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLBodyElement where
fromJSVal v = fmap HTMLBodyElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLBodyElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLBodyElement where
makeObject = makeObject . unHTMLBodyElement
instance IsHTMLElement HTMLBodyElement
instance IsElement HTMLBodyElement
instance IsNode HTMLBodyElement
instance IsEventTarget HTMLBodyElement
instance IsSlotable HTMLBodyElement
instance IsParentNode HTMLBodyElement
instance IsNonDocumentTypeChildNode HTMLBodyElement
instance IsDocumentAndElementEventHandlers HTMLBodyElement
instance IsChildNode HTMLBodyElement
instance IsAnimatable HTMLBodyElement
instance IsGlobalEventHandlers HTMLBodyElement
instance IsElementCSSInlineStyle HTMLBodyElement
instance IsWindowEventHandlers HTMLBodyElement
instance IsGObject HTMLBodyElement where
typeGType _ = gTypeHTMLBodyElement
{-# INLINE typeGType #-}
noHTMLBodyElement :: Maybe HTMLBodyElement
noHTMLBodyElement = Nothing
{-# INLINE noHTMLBodyElement #-}
gTypeHTMLBodyElement :: JSM GType
gTypeHTMLBodyElement = GType . Object <$> jsg "HTMLBodyElement"
newtype HTMLButtonElement = HTMLButtonElement { unHTMLButtonElement :: JSVal }
instance PToJSVal HTMLButtonElement where
pToJSVal = unHTMLButtonElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLButtonElement where
pFromJSVal = HTMLButtonElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLButtonElement where
toJSVal = return . unHTMLButtonElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLButtonElement where
fromJSVal v = fmap HTMLButtonElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLButtonElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLButtonElement where
makeObject = makeObject . unHTMLButtonElement
instance IsHTMLElement HTMLButtonElement
instance IsElement HTMLButtonElement
instance IsNode HTMLButtonElement
instance IsEventTarget HTMLButtonElement
instance IsSlotable HTMLButtonElement
instance IsParentNode HTMLButtonElement
instance IsNonDocumentTypeChildNode HTMLButtonElement
instance IsDocumentAndElementEventHandlers HTMLButtonElement
instance IsChildNode HTMLButtonElement
instance IsAnimatable HTMLButtonElement
instance IsGlobalEventHandlers HTMLButtonElement
instance IsElementCSSInlineStyle HTMLButtonElement
instance IsGObject HTMLButtonElement where
typeGType _ = gTypeHTMLButtonElement
{-# INLINE typeGType #-}
noHTMLButtonElement :: Maybe HTMLButtonElement
noHTMLButtonElement = Nothing
{-# INLINE noHTMLButtonElement #-}
gTypeHTMLButtonElement :: JSM GType
gTypeHTMLButtonElement = GType . Object <$> jsg "HTMLButtonElement"
newtype HTMLCanvasElement = HTMLCanvasElement { unHTMLCanvasElement :: JSVal }
instance PToJSVal HTMLCanvasElement where
pToJSVal = unHTMLCanvasElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLCanvasElement where
pFromJSVal = HTMLCanvasElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLCanvasElement where
toJSVal = return . unHTMLCanvasElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLCanvasElement where
fromJSVal v = fmap HTMLCanvasElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLCanvasElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLCanvasElement where
makeObject = makeObject . unHTMLCanvasElement
instance IsHTMLElement HTMLCanvasElement
instance IsElement HTMLCanvasElement
instance IsNode HTMLCanvasElement
instance IsEventTarget HTMLCanvasElement
instance IsSlotable HTMLCanvasElement
instance IsParentNode HTMLCanvasElement
instance IsNonDocumentTypeChildNode HTMLCanvasElement
instance IsDocumentAndElementEventHandlers HTMLCanvasElement
instance IsChildNode HTMLCanvasElement
instance IsAnimatable HTMLCanvasElement
instance IsGlobalEventHandlers HTMLCanvasElement
instance IsElementCSSInlineStyle HTMLCanvasElement
instance IsGObject HTMLCanvasElement where
typeGType _ = gTypeHTMLCanvasElement
{-# INLINE typeGType #-}
noHTMLCanvasElement :: Maybe HTMLCanvasElement
noHTMLCanvasElement = Nothing
{-# INLINE noHTMLCanvasElement #-}
gTypeHTMLCanvasElement :: JSM GType
gTypeHTMLCanvasElement = GType . Object <$> jsg "HTMLCanvasElement"
newtype HTMLCollection = HTMLCollection { unHTMLCollection :: JSVal }
instance PToJSVal HTMLCollection where
pToJSVal = unHTMLCollection
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLCollection where
pFromJSVal = HTMLCollection
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLCollection where
toJSVal = return . unHTMLCollection
{-# INLINE toJSVal #-}
instance FromJSVal HTMLCollection where
fromJSVal v = fmap HTMLCollection <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLCollection
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLCollection where
makeObject = makeObject . unHTMLCollection
class (IsGObject o) => IsHTMLCollection o
toHTMLCollection :: IsHTMLCollection o => o -> HTMLCollection
toHTMLCollection = HTMLCollection . coerce
instance IsHTMLCollection HTMLCollection
instance IsGObject HTMLCollection where
typeGType _ = gTypeHTMLCollection
{-# INLINE typeGType #-}
noHTMLCollection :: Maybe HTMLCollection
noHTMLCollection = Nothing
{-# INLINE noHTMLCollection #-}
gTypeHTMLCollection :: JSM GType
gTypeHTMLCollection = GType . Object <$> jsg "HTMLCollection"
newtype HTMLDListElement = HTMLDListElement { unHTMLDListElement :: JSVal }
instance PToJSVal HTMLDListElement where
pToJSVal = unHTMLDListElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLDListElement where
pFromJSVal = HTMLDListElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLDListElement where
toJSVal = return . unHTMLDListElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLDListElement where
fromJSVal v = fmap HTMLDListElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLDListElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLDListElement where
makeObject = makeObject . unHTMLDListElement
instance IsHTMLElement HTMLDListElement
instance IsElement HTMLDListElement
instance IsNode HTMLDListElement
instance IsEventTarget HTMLDListElement
instance IsSlotable HTMLDListElement
instance IsParentNode HTMLDListElement
instance IsNonDocumentTypeChildNode HTMLDListElement
instance IsDocumentAndElementEventHandlers HTMLDListElement
instance IsChildNode HTMLDListElement
instance IsAnimatable HTMLDListElement
instance IsGlobalEventHandlers HTMLDListElement
instance IsElementCSSInlineStyle HTMLDListElement
instance IsGObject HTMLDListElement where
typeGType _ = gTypeHTMLDListElement
{-# INLINE typeGType #-}
noHTMLDListElement :: Maybe HTMLDListElement
noHTMLDListElement = Nothing
{-# INLINE noHTMLDListElement #-}
gTypeHTMLDListElement :: JSM GType
gTypeHTMLDListElement = GType . Object <$> jsg "HTMLDListElement"
newtype HTMLDataElement = HTMLDataElement { unHTMLDataElement :: JSVal }
instance PToJSVal HTMLDataElement where
pToJSVal = unHTMLDataElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLDataElement where
pFromJSVal = HTMLDataElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLDataElement where
toJSVal = return . unHTMLDataElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLDataElement where
fromJSVal v = fmap HTMLDataElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLDataElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLDataElement where
makeObject = makeObject . unHTMLDataElement
instance IsHTMLElement HTMLDataElement
instance IsElement HTMLDataElement
instance IsNode HTMLDataElement
instance IsEventTarget HTMLDataElement
instance IsSlotable HTMLDataElement
instance IsParentNode HTMLDataElement
instance IsNonDocumentTypeChildNode HTMLDataElement
instance IsDocumentAndElementEventHandlers HTMLDataElement
instance IsChildNode HTMLDataElement
instance IsAnimatable HTMLDataElement
instance IsGlobalEventHandlers HTMLDataElement
instance IsElementCSSInlineStyle HTMLDataElement
instance IsGObject HTMLDataElement where
typeGType _ = gTypeHTMLDataElement
{-# INLINE typeGType #-}
noHTMLDataElement :: Maybe HTMLDataElement
noHTMLDataElement = Nothing
{-# INLINE noHTMLDataElement #-}
gTypeHTMLDataElement :: JSM GType
gTypeHTMLDataElement = GType . Object <$> jsg "HTMLDataElement"
newtype HTMLDataListElement = HTMLDataListElement { unHTMLDataListElement :: JSVal }
instance PToJSVal HTMLDataListElement where
pToJSVal = unHTMLDataListElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLDataListElement where
pFromJSVal = HTMLDataListElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLDataListElement where
toJSVal = return . unHTMLDataListElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLDataListElement where
fromJSVal v = fmap HTMLDataListElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLDataListElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLDataListElement where
makeObject = makeObject . unHTMLDataListElement
instance IsHTMLElement HTMLDataListElement
instance IsElement HTMLDataListElement
instance IsNode HTMLDataListElement
instance IsEventTarget HTMLDataListElement
instance IsSlotable HTMLDataListElement
instance IsParentNode HTMLDataListElement
instance IsNonDocumentTypeChildNode HTMLDataListElement
instance IsDocumentAndElementEventHandlers HTMLDataListElement
instance IsChildNode HTMLDataListElement
instance IsAnimatable HTMLDataListElement
instance IsGlobalEventHandlers HTMLDataListElement
instance IsElementCSSInlineStyle HTMLDataListElement
instance IsGObject HTMLDataListElement where
typeGType _ = gTypeHTMLDataListElement
{-# INLINE typeGType #-}
noHTMLDataListElement :: Maybe HTMLDataListElement
noHTMLDataListElement = Nothing
{-# INLINE noHTMLDataListElement #-}
gTypeHTMLDataListElement :: JSM GType
gTypeHTMLDataListElement = GType . Object <$> jsg "HTMLDataListElement"
newtype HTMLDetailsElement = HTMLDetailsElement { unHTMLDetailsElement :: JSVal }
instance PToJSVal HTMLDetailsElement where
pToJSVal = unHTMLDetailsElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLDetailsElement where
pFromJSVal = HTMLDetailsElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLDetailsElement where
toJSVal = return . unHTMLDetailsElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLDetailsElement where
fromJSVal v = fmap HTMLDetailsElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLDetailsElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLDetailsElement where
makeObject = makeObject . unHTMLDetailsElement
instance IsHTMLElement HTMLDetailsElement
instance IsElement HTMLDetailsElement
instance IsNode HTMLDetailsElement
instance IsEventTarget HTMLDetailsElement
instance IsSlotable HTMLDetailsElement
instance IsParentNode HTMLDetailsElement
instance IsNonDocumentTypeChildNode HTMLDetailsElement
instance IsDocumentAndElementEventHandlers HTMLDetailsElement
instance IsChildNode HTMLDetailsElement
instance IsAnimatable HTMLDetailsElement
instance IsGlobalEventHandlers HTMLDetailsElement
instance IsElementCSSInlineStyle HTMLDetailsElement
instance IsGObject HTMLDetailsElement where
typeGType _ = gTypeHTMLDetailsElement
{-# INLINE typeGType #-}
noHTMLDetailsElement :: Maybe HTMLDetailsElement
noHTMLDetailsElement = Nothing
{-# INLINE noHTMLDetailsElement #-}
gTypeHTMLDetailsElement :: JSM GType
gTypeHTMLDetailsElement = GType . Object <$> jsg "HTMLDetailsElement"
newtype HTMLDirectoryElement = HTMLDirectoryElement { unHTMLDirectoryElement :: JSVal }
instance PToJSVal HTMLDirectoryElement where
pToJSVal = unHTMLDirectoryElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLDirectoryElement where
pFromJSVal = HTMLDirectoryElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLDirectoryElement where
toJSVal = return . unHTMLDirectoryElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLDirectoryElement where
fromJSVal v = fmap HTMLDirectoryElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLDirectoryElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLDirectoryElement where
makeObject = makeObject . unHTMLDirectoryElement
instance IsHTMLElement HTMLDirectoryElement
instance IsElement HTMLDirectoryElement
instance IsNode HTMLDirectoryElement
instance IsEventTarget HTMLDirectoryElement
instance IsSlotable HTMLDirectoryElement
instance IsParentNode HTMLDirectoryElement
instance IsNonDocumentTypeChildNode HTMLDirectoryElement
instance IsDocumentAndElementEventHandlers HTMLDirectoryElement
instance IsChildNode HTMLDirectoryElement
instance IsAnimatable HTMLDirectoryElement
instance IsGlobalEventHandlers HTMLDirectoryElement
instance IsElementCSSInlineStyle HTMLDirectoryElement
instance IsGObject HTMLDirectoryElement where
typeGType _ = gTypeHTMLDirectoryElement
{-# INLINE typeGType #-}
noHTMLDirectoryElement :: Maybe HTMLDirectoryElement
noHTMLDirectoryElement = Nothing
{-# INLINE noHTMLDirectoryElement #-}
gTypeHTMLDirectoryElement :: JSM GType
gTypeHTMLDirectoryElement = GType . Object <$> jsg "HTMLDirectoryElement"
newtype HTMLDivElement = HTMLDivElement { unHTMLDivElement :: JSVal }
instance PToJSVal HTMLDivElement where
pToJSVal = unHTMLDivElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLDivElement where
pFromJSVal = HTMLDivElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLDivElement where
toJSVal = return . unHTMLDivElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLDivElement where
fromJSVal v = fmap HTMLDivElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLDivElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLDivElement where
makeObject = makeObject . unHTMLDivElement
instance IsHTMLElement HTMLDivElement
instance IsElement HTMLDivElement
instance IsNode HTMLDivElement
instance IsEventTarget HTMLDivElement
instance IsSlotable HTMLDivElement
instance IsParentNode HTMLDivElement
instance IsNonDocumentTypeChildNode HTMLDivElement
instance IsDocumentAndElementEventHandlers HTMLDivElement
instance IsChildNode HTMLDivElement
instance IsAnimatable HTMLDivElement
instance IsGlobalEventHandlers HTMLDivElement
instance IsElementCSSInlineStyle HTMLDivElement
instance IsGObject HTMLDivElement where
typeGType _ = gTypeHTMLDivElement
{-# INLINE typeGType #-}
noHTMLDivElement :: Maybe HTMLDivElement
noHTMLDivElement = Nothing
{-# INLINE noHTMLDivElement #-}
gTypeHTMLDivElement :: JSM GType
gTypeHTMLDivElement = GType . Object <$> jsg "HTMLDivElement"
newtype HTMLDocument = HTMLDocument { unHTMLDocument :: JSVal }
instance PToJSVal HTMLDocument where
pToJSVal = unHTMLDocument
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLDocument where
pFromJSVal = HTMLDocument
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLDocument where
toJSVal = return . unHTMLDocument
{-# INLINE toJSVal #-}
instance FromJSVal HTMLDocument where
fromJSVal v = fmap HTMLDocument <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLDocument
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLDocument where
makeObject = makeObject . unHTMLDocument
instance IsDocument HTMLDocument
instance IsNode HTMLDocument
instance IsEventTarget HTMLDocument
instance IsGlobalEventHandlers HTMLDocument
instance IsDocumentOrShadowRoot HTMLDocument
instance IsNonElementParentNode HTMLDocument
instance IsParentNode HTMLDocument
instance IsDocumentAndElementEventHandlers HTMLDocument
instance IsGObject HTMLDocument where
typeGType _ = gTypeHTMLDocument
{-# INLINE typeGType #-}
noHTMLDocument :: Maybe HTMLDocument
noHTMLDocument = Nothing
{-# INLINE noHTMLDocument #-}
gTypeHTMLDocument :: JSM GType
gTypeHTMLDocument = GType . Object <$> jsg "HTMLDocument"
newtype HTMLElement = HTMLElement { unHTMLElement :: JSVal }
instance PToJSVal HTMLElement where
pToJSVal = unHTMLElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLElement where
pFromJSVal = HTMLElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLElement where
toJSVal = return . unHTMLElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLElement where
fromJSVal v = fmap HTMLElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLElement where
makeObject = makeObject . unHTMLElement
class (IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsGObject o) => IsHTMLElement o
toHTMLElement :: IsHTMLElement o => o -> HTMLElement
toHTMLElement = HTMLElement . coerce
instance IsHTMLElement HTMLElement
instance IsElement HTMLElement
instance IsNode HTMLElement
instance IsEventTarget HTMLElement
instance IsSlotable HTMLElement
instance IsParentNode HTMLElement
instance IsNonDocumentTypeChildNode HTMLElement
instance IsDocumentAndElementEventHandlers HTMLElement
instance IsChildNode HTMLElement
instance IsAnimatable HTMLElement
instance IsGlobalEventHandlers HTMLElement
instance IsElementCSSInlineStyle HTMLElement
instance IsGObject HTMLElement where
typeGType _ = gTypeHTMLElement
{-# INLINE typeGType #-}
noHTMLElement :: Maybe HTMLElement
noHTMLElement = Nothing
{-# INLINE noHTMLElement #-}
gTypeHTMLElement :: JSM GType
gTypeHTMLElement = GType . Object <$> jsg "HTMLElement"
newtype HTMLEmbedElement = HTMLEmbedElement { unHTMLEmbedElement :: JSVal }
instance PToJSVal HTMLEmbedElement where
pToJSVal = unHTMLEmbedElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLEmbedElement where
pFromJSVal = HTMLEmbedElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLEmbedElement where
toJSVal = return . unHTMLEmbedElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLEmbedElement where
fromJSVal v = fmap HTMLEmbedElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLEmbedElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLEmbedElement where
makeObject = makeObject . unHTMLEmbedElement
instance IsHTMLElement HTMLEmbedElement
instance IsElement HTMLEmbedElement
instance IsNode HTMLEmbedElement
instance IsEventTarget HTMLEmbedElement
instance IsSlotable HTMLEmbedElement
instance IsParentNode HTMLEmbedElement
instance IsNonDocumentTypeChildNode HTMLEmbedElement
instance IsDocumentAndElementEventHandlers HTMLEmbedElement
instance IsChildNode HTMLEmbedElement
instance IsAnimatable HTMLEmbedElement
instance IsGlobalEventHandlers HTMLEmbedElement
instance IsElementCSSInlineStyle HTMLEmbedElement
instance IsGObject HTMLEmbedElement where
typeGType _ = gTypeHTMLEmbedElement
{-# INLINE typeGType #-}
noHTMLEmbedElement :: Maybe HTMLEmbedElement
noHTMLEmbedElement = Nothing
{-# INLINE noHTMLEmbedElement #-}
gTypeHTMLEmbedElement :: JSM GType
gTypeHTMLEmbedElement = GType . Object <$> jsg "HTMLEmbedElement"
newtype HTMLFieldSetElement = HTMLFieldSetElement { unHTMLFieldSetElement :: JSVal }
instance PToJSVal HTMLFieldSetElement where
pToJSVal = unHTMLFieldSetElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLFieldSetElement where
pFromJSVal = HTMLFieldSetElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLFieldSetElement where
toJSVal = return . unHTMLFieldSetElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLFieldSetElement where
fromJSVal v = fmap HTMLFieldSetElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLFieldSetElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLFieldSetElement where
makeObject = makeObject . unHTMLFieldSetElement
instance IsHTMLElement HTMLFieldSetElement
instance IsElement HTMLFieldSetElement
instance IsNode HTMLFieldSetElement
instance IsEventTarget HTMLFieldSetElement
instance IsSlotable HTMLFieldSetElement
instance IsParentNode HTMLFieldSetElement
instance IsNonDocumentTypeChildNode HTMLFieldSetElement
instance IsDocumentAndElementEventHandlers HTMLFieldSetElement
instance IsChildNode HTMLFieldSetElement
instance IsAnimatable HTMLFieldSetElement
instance IsGlobalEventHandlers HTMLFieldSetElement
instance IsElementCSSInlineStyle HTMLFieldSetElement
instance IsGObject HTMLFieldSetElement where
typeGType _ = gTypeHTMLFieldSetElement
{-# INLINE typeGType #-}
noHTMLFieldSetElement :: Maybe HTMLFieldSetElement
noHTMLFieldSetElement = Nothing
{-# INLINE noHTMLFieldSetElement #-}
gTypeHTMLFieldSetElement :: JSM GType
gTypeHTMLFieldSetElement = GType . Object <$> jsg "HTMLFieldSetElement"
newtype HTMLFontElement = HTMLFontElement { unHTMLFontElement :: JSVal }
instance PToJSVal HTMLFontElement where
pToJSVal = unHTMLFontElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLFontElement where
pFromJSVal = HTMLFontElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLFontElement where
toJSVal = return . unHTMLFontElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLFontElement where
fromJSVal v = fmap HTMLFontElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLFontElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLFontElement where
makeObject = makeObject . unHTMLFontElement
instance IsHTMLElement HTMLFontElement
instance IsElement HTMLFontElement
instance IsNode HTMLFontElement
instance IsEventTarget HTMLFontElement
instance IsSlotable HTMLFontElement
instance IsParentNode HTMLFontElement
instance IsNonDocumentTypeChildNode HTMLFontElement
instance IsDocumentAndElementEventHandlers HTMLFontElement
instance IsChildNode HTMLFontElement
instance IsAnimatable HTMLFontElement
instance IsGlobalEventHandlers HTMLFontElement
instance IsElementCSSInlineStyle HTMLFontElement
instance IsGObject HTMLFontElement where
typeGType _ = gTypeHTMLFontElement
{-# INLINE typeGType #-}
noHTMLFontElement :: Maybe HTMLFontElement
noHTMLFontElement = Nothing
{-# INLINE noHTMLFontElement #-}
gTypeHTMLFontElement :: JSM GType
gTypeHTMLFontElement = GType . Object <$> jsg "HTMLFontElement"
newtype HTMLFormControlsCollection = HTMLFormControlsCollection { unHTMLFormControlsCollection :: JSVal }
instance PToJSVal HTMLFormControlsCollection where
pToJSVal = unHTMLFormControlsCollection
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLFormControlsCollection where
pFromJSVal = HTMLFormControlsCollection
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLFormControlsCollection where
toJSVal = return . unHTMLFormControlsCollection
{-# INLINE toJSVal #-}
instance FromJSVal HTMLFormControlsCollection where
fromJSVal v = fmap HTMLFormControlsCollection <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLFormControlsCollection
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLFormControlsCollection where
makeObject = makeObject . unHTMLFormControlsCollection
instance IsHTMLCollection HTMLFormControlsCollection
instance IsGObject HTMLFormControlsCollection where
typeGType _ = gTypeHTMLFormControlsCollection
{-# INLINE typeGType #-}
noHTMLFormControlsCollection :: Maybe HTMLFormControlsCollection
noHTMLFormControlsCollection = Nothing
{-# INLINE noHTMLFormControlsCollection #-}
gTypeHTMLFormControlsCollection :: JSM GType
gTypeHTMLFormControlsCollection = GType . Object <$> jsg "HTMLFormControlsCollection"
newtype HTMLFormElement = HTMLFormElement { unHTMLFormElement :: JSVal }
instance PToJSVal HTMLFormElement where
pToJSVal = unHTMLFormElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLFormElement where
pFromJSVal = HTMLFormElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLFormElement where
toJSVal = return . unHTMLFormElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLFormElement where
fromJSVal v = fmap HTMLFormElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLFormElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLFormElement where
makeObject = makeObject . unHTMLFormElement
instance IsHTMLElement HTMLFormElement
instance IsElement HTMLFormElement
instance IsNode HTMLFormElement
instance IsEventTarget HTMLFormElement
instance IsSlotable HTMLFormElement
instance IsParentNode HTMLFormElement
instance IsNonDocumentTypeChildNode HTMLFormElement
instance IsDocumentAndElementEventHandlers HTMLFormElement
instance IsChildNode HTMLFormElement
instance IsAnimatable HTMLFormElement
instance IsGlobalEventHandlers HTMLFormElement
instance IsElementCSSInlineStyle HTMLFormElement
instance IsGObject HTMLFormElement where
typeGType _ = gTypeHTMLFormElement
{-# INLINE typeGType #-}
noHTMLFormElement :: Maybe HTMLFormElement
noHTMLFormElement = Nothing
{-# INLINE noHTMLFormElement #-}
gTypeHTMLFormElement :: JSM GType
gTypeHTMLFormElement = GType . Object <$> jsg "HTMLFormElement"
newtype HTMLFrameElement = HTMLFrameElement { unHTMLFrameElement :: JSVal }
instance PToJSVal HTMLFrameElement where
pToJSVal = unHTMLFrameElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLFrameElement where
pFromJSVal = HTMLFrameElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLFrameElement where
toJSVal = return . unHTMLFrameElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLFrameElement where
fromJSVal v = fmap HTMLFrameElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLFrameElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLFrameElement where
makeObject = makeObject . unHTMLFrameElement
instance IsHTMLElement HTMLFrameElement
instance IsElement HTMLFrameElement
instance IsNode HTMLFrameElement
instance IsEventTarget HTMLFrameElement
instance IsSlotable HTMLFrameElement
instance IsParentNode HTMLFrameElement
instance IsNonDocumentTypeChildNode HTMLFrameElement
instance IsDocumentAndElementEventHandlers HTMLFrameElement
instance IsChildNode HTMLFrameElement
instance IsAnimatable HTMLFrameElement
instance IsGlobalEventHandlers HTMLFrameElement
instance IsElementCSSInlineStyle HTMLFrameElement
instance IsGObject HTMLFrameElement where
typeGType _ = gTypeHTMLFrameElement
{-# INLINE typeGType #-}
noHTMLFrameElement :: Maybe HTMLFrameElement
noHTMLFrameElement = Nothing
{-# INLINE noHTMLFrameElement #-}
gTypeHTMLFrameElement :: JSM GType
gTypeHTMLFrameElement = GType . Object <$> jsg "HTMLFrameElement"
newtype HTMLFrameSetElement = HTMLFrameSetElement { unHTMLFrameSetElement :: JSVal }
instance PToJSVal HTMLFrameSetElement where
pToJSVal = unHTMLFrameSetElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLFrameSetElement where
pFromJSVal = HTMLFrameSetElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLFrameSetElement where
toJSVal = return . unHTMLFrameSetElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLFrameSetElement where
fromJSVal v = fmap HTMLFrameSetElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLFrameSetElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLFrameSetElement where
makeObject = makeObject . unHTMLFrameSetElement
instance IsHTMLElement HTMLFrameSetElement
instance IsElement HTMLFrameSetElement
instance IsNode HTMLFrameSetElement
instance IsEventTarget HTMLFrameSetElement
instance IsSlotable HTMLFrameSetElement
instance IsParentNode HTMLFrameSetElement
instance IsNonDocumentTypeChildNode HTMLFrameSetElement
instance IsDocumentAndElementEventHandlers HTMLFrameSetElement
instance IsChildNode HTMLFrameSetElement
instance IsAnimatable HTMLFrameSetElement
instance IsGlobalEventHandlers HTMLFrameSetElement
instance IsElementCSSInlineStyle HTMLFrameSetElement
instance IsWindowEventHandlers HTMLFrameSetElement
instance IsGObject HTMLFrameSetElement where
typeGType _ = gTypeHTMLFrameSetElement
{-# INLINE typeGType #-}
noHTMLFrameSetElement :: Maybe HTMLFrameSetElement
noHTMLFrameSetElement = Nothing
{-# INLINE noHTMLFrameSetElement #-}
gTypeHTMLFrameSetElement :: JSM GType
gTypeHTMLFrameSetElement = GType . Object <$> jsg "HTMLFrameSetElement"
newtype HTMLHRElement = HTMLHRElement { unHTMLHRElement :: JSVal }
instance PToJSVal HTMLHRElement where
pToJSVal = unHTMLHRElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLHRElement where
pFromJSVal = HTMLHRElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLHRElement where
toJSVal = return . unHTMLHRElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLHRElement where
fromJSVal v = fmap HTMLHRElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLHRElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLHRElement where
makeObject = makeObject . unHTMLHRElement
instance IsHTMLElement HTMLHRElement
instance IsElement HTMLHRElement
instance IsNode HTMLHRElement
instance IsEventTarget HTMLHRElement
instance IsSlotable HTMLHRElement
instance IsParentNode HTMLHRElement
instance IsNonDocumentTypeChildNode HTMLHRElement
instance IsDocumentAndElementEventHandlers HTMLHRElement
instance IsChildNode HTMLHRElement
instance IsAnimatable HTMLHRElement
instance IsGlobalEventHandlers HTMLHRElement
instance IsElementCSSInlineStyle HTMLHRElement
instance IsGObject HTMLHRElement where
typeGType _ = gTypeHTMLHRElement
{-# INLINE typeGType #-}
noHTMLHRElement :: Maybe HTMLHRElement
noHTMLHRElement = Nothing
{-# INLINE noHTMLHRElement #-}
gTypeHTMLHRElement :: JSM GType
gTypeHTMLHRElement = GType . Object <$> jsg "HTMLHRElement"
newtype HTMLHeadElement = HTMLHeadElement { unHTMLHeadElement :: JSVal }
instance PToJSVal HTMLHeadElement where
pToJSVal = unHTMLHeadElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLHeadElement where
pFromJSVal = HTMLHeadElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLHeadElement where
toJSVal = return . unHTMLHeadElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLHeadElement where
fromJSVal v = fmap HTMLHeadElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLHeadElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLHeadElement where
makeObject = makeObject . unHTMLHeadElement
instance IsHTMLElement HTMLHeadElement
instance IsElement HTMLHeadElement
instance IsNode HTMLHeadElement
instance IsEventTarget HTMLHeadElement
instance IsSlotable HTMLHeadElement
instance IsParentNode HTMLHeadElement
instance IsNonDocumentTypeChildNode HTMLHeadElement
instance IsDocumentAndElementEventHandlers HTMLHeadElement
instance IsChildNode HTMLHeadElement
instance IsAnimatable HTMLHeadElement
instance IsGlobalEventHandlers HTMLHeadElement
instance IsElementCSSInlineStyle HTMLHeadElement
instance IsGObject HTMLHeadElement where
typeGType _ = gTypeHTMLHeadElement
{-# INLINE typeGType #-}
noHTMLHeadElement :: Maybe HTMLHeadElement
noHTMLHeadElement = Nothing
{-# INLINE noHTMLHeadElement #-}
gTypeHTMLHeadElement :: JSM GType
gTypeHTMLHeadElement = GType . Object <$> jsg "HTMLHeadElement"
newtype HTMLHeadingElement = HTMLHeadingElement { unHTMLHeadingElement :: JSVal }
instance PToJSVal HTMLHeadingElement where
pToJSVal = unHTMLHeadingElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLHeadingElement where
pFromJSVal = HTMLHeadingElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLHeadingElement where
toJSVal = return . unHTMLHeadingElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLHeadingElement where
fromJSVal v = fmap HTMLHeadingElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLHeadingElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLHeadingElement where
makeObject = makeObject . unHTMLHeadingElement
instance IsHTMLElement HTMLHeadingElement
instance IsElement HTMLHeadingElement
instance IsNode HTMLHeadingElement
instance IsEventTarget HTMLHeadingElement
instance IsSlotable HTMLHeadingElement
instance IsParentNode HTMLHeadingElement
instance IsNonDocumentTypeChildNode HTMLHeadingElement
instance IsDocumentAndElementEventHandlers HTMLHeadingElement
instance IsChildNode HTMLHeadingElement
instance IsAnimatable HTMLHeadingElement
instance IsGlobalEventHandlers HTMLHeadingElement
instance IsElementCSSInlineStyle HTMLHeadingElement
instance IsGObject HTMLHeadingElement where
typeGType _ = gTypeHTMLHeadingElement
{-# INLINE typeGType #-}
noHTMLHeadingElement :: Maybe HTMLHeadingElement
noHTMLHeadingElement = Nothing
{-# INLINE noHTMLHeadingElement #-}
gTypeHTMLHeadingElement :: JSM GType
gTypeHTMLHeadingElement = GType . Object <$> jsg "HTMLHeadingElement"
newtype HTMLHtmlElement = HTMLHtmlElement { unHTMLHtmlElement :: JSVal }
instance PToJSVal HTMLHtmlElement where
pToJSVal = unHTMLHtmlElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLHtmlElement where
pFromJSVal = HTMLHtmlElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLHtmlElement where
toJSVal = return . unHTMLHtmlElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLHtmlElement where
fromJSVal v = fmap HTMLHtmlElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLHtmlElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLHtmlElement where
makeObject = makeObject . unHTMLHtmlElement
instance IsHTMLElement HTMLHtmlElement
instance IsElement HTMLHtmlElement
instance IsNode HTMLHtmlElement
instance IsEventTarget HTMLHtmlElement
instance IsSlotable HTMLHtmlElement
instance IsParentNode HTMLHtmlElement
instance IsNonDocumentTypeChildNode HTMLHtmlElement
instance IsDocumentAndElementEventHandlers HTMLHtmlElement
instance IsChildNode HTMLHtmlElement
instance IsAnimatable HTMLHtmlElement
instance IsGlobalEventHandlers HTMLHtmlElement
instance IsElementCSSInlineStyle HTMLHtmlElement
instance IsGObject HTMLHtmlElement where
typeGType _ = gTypeHTMLHtmlElement
{-# INLINE typeGType #-}
noHTMLHtmlElement :: Maybe HTMLHtmlElement
noHTMLHtmlElement = Nothing
{-# INLINE noHTMLHtmlElement #-}
gTypeHTMLHtmlElement :: JSM GType
gTypeHTMLHtmlElement = GType . Object <$> jsg "HTMLHtmlElement"
newtype HTMLHyperlinkElementUtils = HTMLHyperlinkElementUtils { unHTMLHyperlinkElementUtils :: JSVal }
instance PToJSVal HTMLHyperlinkElementUtils where
pToJSVal = unHTMLHyperlinkElementUtils
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLHyperlinkElementUtils where
pFromJSVal = HTMLHyperlinkElementUtils
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLHyperlinkElementUtils where
toJSVal = return . unHTMLHyperlinkElementUtils
{-# INLINE toJSVal #-}
instance FromJSVal HTMLHyperlinkElementUtils where
fromJSVal v = fmap HTMLHyperlinkElementUtils <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLHyperlinkElementUtils
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLHyperlinkElementUtils where
makeObject = makeObject . unHTMLHyperlinkElementUtils
class (IsGObject o) => IsHTMLHyperlinkElementUtils o
toHTMLHyperlinkElementUtils :: IsHTMLHyperlinkElementUtils o => o -> HTMLHyperlinkElementUtils
toHTMLHyperlinkElementUtils = HTMLHyperlinkElementUtils . coerce
instance IsHTMLHyperlinkElementUtils HTMLHyperlinkElementUtils
instance IsGObject HTMLHyperlinkElementUtils where
typeGType _ = gTypeHTMLHyperlinkElementUtils
{-# INLINE typeGType #-}
noHTMLHyperlinkElementUtils :: Maybe HTMLHyperlinkElementUtils
noHTMLHyperlinkElementUtils = Nothing
{-# INLINE noHTMLHyperlinkElementUtils #-}
gTypeHTMLHyperlinkElementUtils :: JSM GType
gTypeHTMLHyperlinkElementUtils = GType . Object <$> jsg "HTMLHyperlinkElementUtils"
newtype HTMLIFrameElement = HTMLIFrameElement { unHTMLIFrameElement :: JSVal }
instance PToJSVal HTMLIFrameElement where
pToJSVal = unHTMLIFrameElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLIFrameElement where
pFromJSVal = HTMLIFrameElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLIFrameElement where
toJSVal = return . unHTMLIFrameElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLIFrameElement where
fromJSVal v = fmap HTMLIFrameElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLIFrameElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLIFrameElement where
makeObject = makeObject . unHTMLIFrameElement
instance IsHTMLElement HTMLIFrameElement
instance IsElement HTMLIFrameElement
instance IsNode HTMLIFrameElement
instance IsEventTarget HTMLIFrameElement
instance IsSlotable HTMLIFrameElement
instance IsParentNode HTMLIFrameElement
instance IsNonDocumentTypeChildNode HTMLIFrameElement
instance IsDocumentAndElementEventHandlers HTMLIFrameElement
instance IsChildNode HTMLIFrameElement
instance IsAnimatable HTMLIFrameElement
instance IsGlobalEventHandlers HTMLIFrameElement
instance IsElementCSSInlineStyle HTMLIFrameElement
instance IsGObject HTMLIFrameElement where
typeGType _ = gTypeHTMLIFrameElement
{-# INLINE typeGType #-}
noHTMLIFrameElement :: Maybe HTMLIFrameElement
noHTMLIFrameElement = Nothing
{-# INLINE noHTMLIFrameElement #-}
gTypeHTMLIFrameElement :: JSM GType
gTypeHTMLIFrameElement = GType . Object <$> jsg "HTMLIFrameElement"
newtype HTMLImageElement = HTMLImageElement { unHTMLImageElement :: JSVal }
instance PToJSVal HTMLImageElement where
pToJSVal = unHTMLImageElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLImageElement where
pFromJSVal = HTMLImageElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLImageElement where
toJSVal = return . unHTMLImageElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLImageElement where
fromJSVal v = fmap HTMLImageElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLImageElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLImageElement where
makeObject = makeObject . unHTMLImageElement
instance IsHTMLElement HTMLImageElement
instance IsElement HTMLImageElement
instance IsNode HTMLImageElement
instance IsEventTarget HTMLImageElement
instance IsSlotable HTMLImageElement
instance IsParentNode HTMLImageElement
instance IsNonDocumentTypeChildNode HTMLImageElement
instance IsDocumentAndElementEventHandlers HTMLImageElement
instance IsChildNode HTMLImageElement
instance IsAnimatable HTMLImageElement
instance IsGlobalEventHandlers HTMLImageElement
instance IsElementCSSInlineStyle HTMLImageElement
instance IsGObject HTMLImageElement where
typeGType _ = gTypeHTMLImageElement
{-# INLINE typeGType #-}
noHTMLImageElement :: Maybe HTMLImageElement
noHTMLImageElement = Nothing
{-# INLINE noHTMLImageElement #-}
gTypeHTMLImageElement :: JSM GType
gTypeHTMLImageElement = GType . Object <$> jsg "HTMLImageElement"
newtype HTMLInputElement = HTMLInputElement { unHTMLInputElement :: JSVal }
instance PToJSVal HTMLInputElement where
pToJSVal = unHTMLInputElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLInputElement where
pFromJSVal = HTMLInputElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLInputElement where
toJSVal = return . unHTMLInputElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLInputElement where
fromJSVal v = fmap HTMLInputElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLInputElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLInputElement where
makeObject = makeObject . unHTMLInputElement
instance IsHTMLElement HTMLInputElement
instance IsElement HTMLInputElement
instance IsNode HTMLInputElement
instance IsEventTarget HTMLInputElement
instance IsSlotable HTMLInputElement
instance IsParentNode HTMLInputElement
instance IsNonDocumentTypeChildNode HTMLInputElement
instance IsDocumentAndElementEventHandlers HTMLInputElement
instance IsChildNode HTMLInputElement
instance IsAnimatable HTMLInputElement
instance IsGlobalEventHandlers HTMLInputElement
instance IsElementCSSInlineStyle HTMLInputElement
instance IsGObject HTMLInputElement where
typeGType _ = gTypeHTMLInputElement
{-# INLINE typeGType #-}
noHTMLInputElement :: Maybe HTMLInputElement
noHTMLInputElement = Nothing
{-# INLINE noHTMLInputElement #-}
gTypeHTMLInputElement :: JSM GType
gTypeHTMLInputElement = GType . Object <$> jsg "HTMLInputElement"
newtype HTMLKeygenElement = HTMLKeygenElement { unHTMLKeygenElement :: JSVal }
instance PToJSVal HTMLKeygenElement where
pToJSVal = unHTMLKeygenElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLKeygenElement where
pFromJSVal = HTMLKeygenElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLKeygenElement where
toJSVal = return . unHTMLKeygenElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLKeygenElement where
fromJSVal v = fmap HTMLKeygenElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLKeygenElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLKeygenElement where
makeObject = makeObject . unHTMLKeygenElement
instance IsHTMLElement HTMLKeygenElement
instance IsElement HTMLKeygenElement
instance IsNode HTMLKeygenElement
instance IsEventTarget HTMLKeygenElement
instance IsSlotable HTMLKeygenElement
instance IsParentNode HTMLKeygenElement
instance IsNonDocumentTypeChildNode HTMLKeygenElement
instance IsDocumentAndElementEventHandlers HTMLKeygenElement
instance IsChildNode HTMLKeygenElement
instance IsAnimatable HTMLKeygenElement
instance IsGlobalEventHandlers HTMLKeygenElement
instance IsElementCSSInlineStyle HTMLKeygenElement
instance IsGObject HTMLKeygenElement where
typeGType _ = gTypeHTMLKeygenElement
{-# INLINE typeGType #-}
noHTMLKeygenElement :: Maybe HTMLKeygenElement
noHTMLKeygenElement = Nothing
{-# INLINE noHTMLKeygenElement #-}
gTypeHTMLKeygenElement :: JSM GType
gTypeHTMLKeygenElement = GType . Object <$> jsg "HTMLKeygenElement"
newtype HTMLLIElement = HTMLLIElement { unHTMLLIElement :: JSVal }
instance PToJSVal HTMLLIElement where
pToJSVal = unHTMLLIElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLLIElement where
pFromJSVal = HTMLLIElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLLIElement where
toJSVal = return . unHTMLLIElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLLIElement where
fromJSVal v = fmap HTMLLIElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLLIElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLLIElement where
makeObject = makeObject . unHTMLLIElement
instance IsHTMLElement HTMLLIElement
instance IsElement HTMLLIElement
instance IsNode HTMLLIElement
instance IsEventTarget HTMLLIElement
instance IsSlotable HTMLLIElement
instance IsParentNode HTMLLIElement
instance IsNonDocumentTypeChildNode HTMLLIElement
instance IsDocumentAndElementEventHandlers HTMLLIElement
instance IsChildNode HTMLLIElement
instance IsAnimatable HTMLLIElement
instance IsGlobalEventHandlers HTMLLIElement
instance IsElementCSSInlineStyle HTMLLIElement
instance IsGObject HTMLLIElement where
typeGType _ = gTypeHTMLLIElement
{-# INLINE typeGType #-}
noHTMLLIElement :: Maybe HTMLLIElement
noHTMLLIElement = Nothing
{-# INLINE noHTMLLIElement #-}
gTypeHTMLLIElement :: JSM GType
gTypeHTMLLIElement = GType . Object <$> jsg "HTMLLIElement"
newtype HTMLLabelElement = HTMLLabelElement { unHTMLLabelElement :: JSVal }
instance PToJSVal HTMLLabelElement where
pToJSVal = unHTMLLabelElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLLabelElement where
pFromJSVal = HTMLLabelElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLLabelElement where
toJSVal = return . unHTMLLabelElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLLabelElement where
fromJSVal v = fmap HTMLLabelElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLLabelElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLLabelElement where
makeObject = makeObject . unHTMLLabelElement
instance IsHTMLElement HTMLLabelElement
instance IsElement HTMLLabelElement
instance IsNode HTMLLabelElement
instance IsEventTarget HTMLLabelElement
instance IsSlotable HTMLLabelElement
instance IsParentNode HTMLLabelElement
instance IsNonDocumentTypeChildNode HTMLLabelElement
instance IsDocumentAndElementEventHandlers HTMLLabelElement
instance IsChildNode HTMLLabelElement
instance IsAnimatable HTMLLabelElement
instance IsGlobalEventHandlers HTMLLabelElement
instance IsElementCSSInlineStyle HTMLLabelElement
instance IsGObject HTMLLabelElement where
typeGType _ = gTypeHTMLLabelElement
{-# INLINE typeGType #-}
noHTMLLabelElement :: Maybe HTMLLabelElement
noHTMLLabelElement = Nothing
{-# INLINE noHTMLLabelElement #-}
gTypeHTMLLabelElement :: JSM GType
gTypeHTMLLabelElement = GType . Object <$> jsg "HTMLLabelElement"
newtype HTMLLegendElement = HTMLLegendElement { unHTMLLegendElement :: JSVal }
instance PToJSVal HTMLLegendElement where
pToJSVal = unHTMLLegendElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLLegendElement where
pFromJSVal = HTMLLegendElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLLegendElement where
toJSVal = return . unHTMLLegendElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLLegendElement where
fromJSVal v = fmap HTMLLegendElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLLegendElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLLegendElement where
makeObject = makeObject . unHTMLLegendElement
instance IsHTMLElement HTMLLegendElement
instance IsElement HTMLLegendElement
instance IsNode HTMLLegendElement
instance IsEventTarget HTMLLegendElement
instance IsSlotable HTMLLegendElement
instance IsParentNode HTMLLegendElement
instance IsNonDocumentTypeChildNode HTMLLegendElement
instance IsDocumentAndElementEventHandlers HTMLLegendElement
instance IsChildNode HTMLLegendElement
instance IsAnimatable HTMLLegendElement
instance IsGlobalEventHandlers HTMLLegendElement
instance IsElementCSSInlineStyle HTMLLegendElement
instance IsGObject HTMLLegendElement where
typeGType _ = gTypeHTMLLegendElement
{-# INLINE typeGType #-}
noHTMLLegendElement :: Maybe HTMLLegendElement
noHTMLLegendElement = Nothing
{-# INLINE noHTMLLegendElement #-}
gTypeHTMLLegendElement :: JSM GType
gTypeHTMLLegendElement = GType . Object <$> jsg "HTMLLegendElement"
newtype HTMLLinkElement = HTMLLinkElement { unHTMLLinkElement :: JSVal }
instance PToJSVal HTMLLinkElement where
pToJSVal = unHTMLLinkElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLLinkElement where
pFromJSVal = HTMLLinkElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLLinkElement where
toJSVal = return . unHTMLLinkElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLLinkElement where
fromJSVal v = fmap HTMLLinkElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLLinkElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLLinkElement where
makeObject = makeObject . unHTMLLinkElement
instance IsHTMLElement HTMLLinkElement
instance IsElement HTMLLinkElement
instance IsNode HTMLLinkElement
instance IsEventTarget HTMLLinkElement
instance IsSlotable HTMLLinkElement
instance IsParentNode HTMLLinkElement
instance IsNonDocumentTypeChildNode HTMLLinkElement
instance IsDocumentAndElementEventHandlers HTMLLinkElement
instance IsChildNode HTMLLinkElement
instance IsAnimatable HTMLLinkElement
instance IsGlobalEventHandlers HTMLLinkElement
instance IsElementCSSInlineStyle HTMLLinkElement
instance IsGObject HTMLLinkElement where
typeGType _ = gTypeHTMLLinkElement
{-# INLINE typeGType #-}
noHTMLLinkElement :: Maybe HTMLLinkElement
noHTMLLinkElement = Nothing
{-# INLINE noHTMLLinkElement #-}
gTypeHTMLLinkElement :: JSM GType
gTypeHTMLLinkElement = GType . Object <$> jsg "HTMLLinkElement"
newtype HTMLMapElement = HTMLMapElement { unHTMLMapElement :: JSVal }
instance PToJSVal HTMLMapElement where
pToJSVal = unHTMLMapElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLMapElement where
pFromJSVal = HTMLMapElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLMapElement where
toJSVal = return . unHTMLMapElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLMapElement where
fromJSVal v = fmap HTMLMapElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLMapElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLMapElement where
makeObject = makeObject . unHTMLMapElement
instance IsHTMLElement HTMLMapElement
instance IsElement HTMLMapElement
instance IsNode HTMLMapElement
instance IsEventTarget HTMLMapElement
instance IsSlotable HTMLMapElement
instance IsParentNode HTMLMapElement
instance IsNonDocumentTypeChildNode HTMLMapElement
instance IsDocumentAndElementEventHandlers HTMLMapElement
instance IsChildNode HTMLMapElement
instance IsAnimatable HTMLMapElement
instance IsGlobalEventHandlers HTMLMapElement
instance IsElementCSSInlineStyle HTMLMapElement
instance IsGObject HTMLMapElement where
typeGType _ = gTypeHTMLMapElement
{-# INLINE typeGType #-}
noHTMLMapElement :: Maybe HTMLMapElement
noHTMLMapElement = Nothing
{-# INLINE noHTMLMapElement #-}
gTypeHTMLMapElement :: JSM GType
gTypeHTMLMapElement = GType . Object <$> jsg "HTMLMapElement"
newtype HTMLMarqueeElement = HTMLMarqueeElement { unHTMLMarqueeElement :: JSVal }
instance PToJSVal HTMLMarqueeElement where
pToJSVal = unHTMLMarqueeElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLMarqueeElement where
pFromJSVal = HTMLMarqueeElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLMarqueeElement where
toJSVal = return . unHTMLMarqueeElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLMarqueeElement where
fromJSVal v = fmap HTMLMarqueeElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLMarqueeElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLMarqueeElement where
makeObject = makeObject . unHTMLMarqueeElement
instance IsHTMLElement HTMLMarqueeElement
instance IsElement HTMLMarqueeElement
instance IsNode HTMLMarqueeElement
instance IsEventTarget HTMLMarqueeElement
instance IsSlotable HTMLMarqueeElement
instance IsParentNode HTMLMarqueeElement
instance IsNonDocumentTypeChildNode HTMLMarqueeElement
instance IsDocumentAndElementEventHandlers HTMLMarqueeElement
instance IsChildNode HTMLMarqueeElement
instance IsAnimatable HTMLMarqueeElement
instance IsGlobalEventHandlers HTMLMarqueeElement
instance IsElementCSSInlineStyle HTMLMarqueeElement
instance IsGObject HTMLMarqueeElement where
typeGType _ = gTypeHTMLMarqueeElement
{-# INLINE typeGType #-}
noHTMLMarqueeElement :: Maybe HTMLMarqueeElement
noHTMLMarqueeElement = Nothing
{-# INLINE noHTMLMarqueeElement #-}
gTypeHTMLMarqueeElement :: JSM GType
gTypeHTMLMarqueeElement = GType . Object <$> jsg "HTMLMarqueeElement"
newtype HTMLMediaElement = HTMLMediaElement { unHTMLMediaElement :: JSVal }
instance PToJSVal HTMLMediaElement where
pToJSVal = unHTMLMediaElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLMediaElement where
pFromJSVal = HTMLMediaElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLMediaElement where
toJSVal = return . unHTMLMediaElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLMediaElement where
fromJSVal v = fmap HTMLMediaElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLMediaElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLMediaElement where
makeObject = makeObject . unHTMLMediaElement
class (IsHTMLElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsGObject o) => IsHTMLMediaElement o
toHTMLMediaElement :: IsHTMLMediaElement o => o -> HTMLMediaElement
toHTMLMediaElement = HTMLMediaElement . coerce
instance IsHTMLMediaElement HTMLMediaElement
instance IsHTMLElement HTMLMediaElement
instance IsElement HTMLMediaElement
instance IsNode HTMLMediaElement
instance IsEventTarget HTMLMediaElement
instance IsSlotable HTMLMediaElement
instance IsParentNode HTMLMediaElement
instance IsNonDocumentTypeChildNode HTMLMediaElement
instance IsDocumentAndElementEventHandlers HTMLMediaElement
instance IsChildNode HTMLMediaElement
instance IsAnimatable HTMLMediaElement
instance IsGlobalEventHandlers HTMLMediaElement
instance IsElementCSSInlineStyle HTMLMediaElement
instance IsGObject HTMLMediaElement where
typeGType _ = gTypeHTMLMediaElement
{-# INLINE typeGType #-}
noHTMLMediaElement :: Maybe HTMLMediaElement
noHTMLMediaElement = Nothing
{-# INLINE noHTMLMediaElement #-}
gTypeHTMLMediaElement :: JSM GType
gTypeHTMLMediaElement = GType . Object <$> jsg "HTMLMediaElement"
newtype HTMLMenuElement = HTMLMenuElement { unHTMLMenuElement :: JSVal }
instance PToJSVal HTMLMenuElement where
pToJSVal = unHTMLMenuElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLMenuElement where
pFromJSVal = HTMLMenuElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLMenuElement where
toJSVal = return . unHTMLMenuElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLMenuElement where
fromJSVal v = fmap HTMLMenuElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLMenuElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLMenuElement where
makeObject = makeObject . unHTMLMenuElement
instance IsHTMLElement HTMLMenuElement
instance IsElement HTMLMenuElement
instance IsNode HTMLMenuElement
instance IsEventTarget HTMLMenuElement
instance IsSlotable HTMLMenuElement
instance IsParentNode HTMLMenuElement
instance IsNonDocumentTypeChildNode HTMLMenuElement
instance IsDocumentAndElementEventHandlers HTMLMenuElement
instance IsChildNode HTMLMenuElement
instance IsAnimatable HTMLMenuElement
instance IsGlobalEventHandlers HTMLMenuElement
instance IsElementCSSInlineStyle HTMLMenuElement
instance IsGObject HTMLMenuElement where
typeGType _ = gTypeHTMLMenuElement
{-# INLINE typeGType #-}
noHTMLMenuElement :: Maybe HTMLMenuElement
noHTMLMenuElement = Nothing
{-# INLINE noHTMLMenuElement #-}
gTypeHTMLMenuElement :: JSM GType
gTypeHTMLMenuElement = GType . Object <$> jsg "HTMLMenuElement"
newtype HTMLMetaElement = HTMLMetaElement { unHTMLMetaElement :: JSVal }
instance PToJSVal HTMLMetaElement where
pToJSVal = unHTMLMetaElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLMetaElement where
pFromJSVal = HTMLMetaElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLMetaElement where
toJSVal = return . unHTMLMetaElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLMetaElement where
fromJSVal v = fmap HTMLMetaElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLMetaElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLMetaElement where
makeObject = makeObject . unHTMLMetaElement
instance IsHTMLElement HTMLMetaElement
instance IsElement HTMLMetaElement
instance IsNode HTMLMetaElement
instance IsEventTarget HTMLMetaElement
instance IsSlotable HTMLMetaElement
instance IsParentNode HTMLMetaElement
instance IsNonDocumentTypeChildNode HTMLMetaElement
instance IsDocumentAndElementEventHandlers HTMLMetaElement
instance IsChildNode HTMLMetaElement
instance IsAnimatable HTMLMetaElement
instance IsGlobalEventHandlers HTMLMetaElement
instance IsElementCSSInlineStyle HTMLMetaElement
instance IsGObject HTMLMetaElement where
typeGType _ = gTypeHTMLMetaElement
{-# INLINE typeGType #-}
noHTMLMetaElement :: Maybe HTMLMetaElement
noHTMLMetaElement = Nothing
{-# INLINE noHTMLMetaElement #-}
gTypeHTMLMetaElement :: JSM GType
gTypeHTMLMetaElement = GType . Object <$> jsg "HTMLMetaElement"
newtype HTMLMeterElement = HTMLMeterElement { unHTMLMeterElement :: JSVal }
instance PToJSVal HTMLMeterElement where
pToJSVal = unHTMLMeterElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLMeterElement where
pFromJSVal = HTMLMeterElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLMeterElement where
toJSVal = return . unHTMLMeterElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLMeterElement where
fromJSVal v = fmap HTMLMeterElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLMeterElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLMeterElement where
makeObject = makeObject . unHTMLMeterElement
instance IsHTMLElement HTMLMeterElement
instance IsElement HTMLMeterElement
instance IsNode HTMLMeterElement
instance IsEventTarget HTMLMeterElement
instance IsSlotable HTMLMeterElement
instance IsParentNode HTMLMeterElement
instance IsNonDocumentTypeChildNode HTMLMeterElement
instance IsDocumentAndElementEventHandlers HTMLMeterElement
instance IsChildNode HTMLMeterElement
instance IsAnimatable HTMLMeterElement
instance IsGlobalEventHandlers HTMLMeterElement
instance IsElementCSSInlineStyle HTMLMeterElement
instance IsGObject HTMLMeterElement where
typeGType _ = gTypeHTMLMeterElement
{-# INLINE typeGType #-}
noHTMLMeterElement :: Maybe HTMLMeterElement
noHTMLMeterElement = Nothing
{-# INLINE noHTMLMeterElement #-}
gTypeHTMLMeterElement :: JSM GType
gTypeHTMLMeterElement = GType . Object <$> jsg "HTMLMeterElement"
newtype HTMLModElement = HTMLModElement { unHTMLModElement :: JSVal }
instance PToJSVal HTMLModElement where
pToJSVal = unHTMLModElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLModElement where
pFromJSVal = HTMLModElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLModElement where
toJSVal = return . unHTMLModElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLModElement where
fromJSVal v = fmap HTMLModElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLModElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLModElement where
makeObject = makeObject . unHTMLModElement
instance IsHTMLElement HTMLModElement
instance IsElement HTMLModElement
instance IsNode HTMLModElement
instance IsEventTarget HTMLModElement
instance IsSlotable HTMLModElement
instance IsParentNode HTMLModElement
instance IsNonDocumentTypeChildNode HTMLModElement
instance IsDocumentAndElementEventHandlers HTMLModElement
instance IsChildNode HTMLModElement
instance IsAnimatable HTMLModElement
instance IsGlobalEventHandlers HTMLModElement
instance IsElementCSSInlineStyle HTMLModElement
instance IsGObject HTMLModElement where
typeGType _ = gTypeHTMLModElement
{-# INLINE typeGType #-}
noHTMLModElement :: Maybe HTMLModElement
noHTMLModElement = Nothing
{-# INLINE noHTMLModElement #-}
gTypeHTMLModElement :: JSM GType
gTypeHTMLModElement = GType . Object <$> jsg "HTMLModElement"
newtype HTMLOListElement = HTMLOListElement { unHTMLOListElement :: JSVal }
instance PToJSVal HTMLOListElement where
pToJSVal = unHTMLOListElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLOListElement where
pFromJSVal = HTMLOListElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLOListElement where
toJSVal = return . unHTMLOListElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLOListElement where
fromJSVal v = fmap HTMLOListElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLOListElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLOListElement where
makeObject = makeObject . unHTMLOListElement
instance IsHTMLElement HTMLOListElement
instance IsElement HTMLOListElement
instance IsNode HTMLOListElement
instance IsEventTarget HTMLOListElement
instance IsSlotable HTMLOListElement
instance IsParentNode HTMLOListElement
instance IsNonDocumentTypeChildNode HTMLOListElement
instance IsDocumentAndElementEventHandlers HTMLOListElement
instance IsChildNode HTMLOListElement
instance IsAnimatable HTMLOListElement
instance IsGlobalEventHandlers HTMLOListElement
instance IsElementCSSInlineStyle HTMLOListElement
instance IsGObject HTMLOListElement where
typeGType _ = gTypeHTMLOListElement
{-# INLINE typeGType #-}
noHTMLOListElement :: Maybe HTMLOListElement
noHTMLOListElement = Nothing
{-# INLINE noHTMLOListElement #-}
gTypeHTMLOListElement :: JSM GType
gTypeHTMLOListElement = GType . Object <$> jsg "HTMLOListElement"
newtype HTMLObjectElement = HTMLObjectElement { unHTMLObjectElement :: JSVal }
instance PToJSVal HTMLObjectElement where
pToJSVal = unHTMLObjectElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLObjectElement where
pFromJSVal = HTMLObjectElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLObjectElement where
toJSVal = return . unHTMLObjectElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLObjectElement where
fromJSVal v = fmap HTMLObjectElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLObjectElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLObjectElement where
makeObject = makeObject . unHTMLObjectElement
instance IsHTMLElement HTMLObjectElement
instance IsElement HTMLObjectElement
instance IsNode HTMLObjectElement
instance IsEventTarget HTMLObjectElement
instance IsSlotable HTMLObjectElement
instance IsParentNode HTMLObjectElement
instance IsNonDocumentTypeChildNode HTMLObjectElement
instance IsDocumentAndElementEventHandlers HTMLObjectElement
instance IsChildNode HTMLObjectElement
instance IsAnimatable HTMLObjectElement
instance IsGlobalEventHandlers HTMLObjectElement
instance IsElementCSSInlineStyle HTMLObjectElement
instance IsGObject HTMLObjectElement where
typeGType _ = gTypeHTMLObjectElement
{-# INLINE typeGType #-}
noHTMLObjectElement :: Maybe HTMLObjectElement
noHTMLObjectElement = Nothing
{-# INLINE noHTMLObjectElement #-}
gTypeHTMLObjectElement :: JSM GType
gTypeHTMLObjectElement = GType . Object <$> jsg "HTMLObjectElement"
newtype HTMLOptGroupElement = HTMLOptGroupElement { unHTMLOptGroupElement :: JSVal }
instance PToJSVal HTMLOptGroupElement where
pToJSVal = unHTMLOptGroupElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLOptGroupElement where
pFromJSVal = HTMLOptGroupElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLOptGroupElement where
toJSVal = return . unHTMLOptGroupElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLOptGroupElement where
fromJSVal v = fmap HTMLOptGroupElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLOptGroupElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLOptGroupElement where
makeObject = makeObject . unHTMLOptGroupElement
instance IsHTMLElement HTMLOptGroupElement
instance IsElement HTMLOptGroupElement
instance IsNode HTMLOptGroupElement
instance IsEventTarget HTMLOptGroupElement
instance IsSlotable HTMLOptGroupElement
instance IsParentNode HTMLOptGroupElement
instance IsNonDocumentTypeChildNode HTMLOptGroupElement
instance IsDocumentAndElementEventHandlers HTMLOptGroupElement
instance IsChildNode HTMLOptGroupElement
instance IsAnimatable HTMLOptGroupElement
instance IsGlobalEventHandlers HTMLOptGroupElement
instance IsElementCSSInlineStyle HTMLOptGroupElement
instance IsGObject HTMLOptGroupElement where
typeGType _ = gTypeHTMLOptGroupElement
{-# INLINE typeGType #-}
noHTMLOptGroupElement :: Maybe HTMLOptGroupElement
noHTMLOptGroupElement = Nothing
{-# INLINE noHTMLOptGroupElement #-}
gTypeHTMLOptGroupElement :: JSM GType
gTypeHTMLOptGroupElement = GType . Object <$> jsg "HTMLOptGroupElement"
newtype HTMLOptionElement = HTMLOptionElement { unHTMLOptionElement :: JSVal }
instance PToJSVal HTMLOptionElement where
pToJSVal = unHTMLOptionElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLOptionElement where
pFromJSVal = HTMLOptionElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLOptionElement where
toJSVal = return . unHTMLOptionElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLOptionElement where
fromJSVal v = fmap HTMLOptionElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLOptionElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLOptionElement where
makeObject = makeObject . unHTMLOptionElement
instance IsHTMLElement HTMLOptionElement
instance IsElement HTMLOptionElement
instance IsNode HTMLOptionElement
instance IsEventTarget HTMLOptionElement
instance IsSlotable HTMLOptionElement
instance IsParentNode HTMLOptionElement
instance IsNonDocumentTypeChildNode HTMLOptionElement
instance IsDocumentAndElementEventHandlers HTMLOptionElement
instance IsChildNode HTMLOptionElement
instance IsAnimatable HTMLOptionElement
instance IsGlobalEventHandlers HTMLOptionElement
instance IsElementCSSInlineStyle HTMLOptionElement
instance IsGObject HTMLOptionElement where
typeGType _ = gTypeHTMLOptionElement
{-# INLINE typeGType #-}
noHTMLOptionElement :: Maybe HTMLOptionElement
noHTMLOptionElement = Nothing
{-# INLINE noHTMLOptionElement #-}
gTypeHTMLOptionElement :: JSM GType
gTypeHTMLOptionElement = GType . Object <$> jsg "HTMLOptionElement"
newtype HTMLOptionsCollection = HTMLOptionsCollection { unHTMLOptionsCollection :: JSVal }
instance PToJSVal HTMLOptionsCollection where
pToJSVal = unHTMLOptionsCollection
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLOptionsCollection where
pFromJSVal = HTMLOptionsCollection
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLOptionsCollection where
toJSVal = return . unHTMLOptionsCollection
{-# INLINE toJSVal #-}
instance FromJSVal HTMLOptionsCollection where
fromJSVal v = fmap HTMLOptionsCollection <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLOptionsCollection
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLOptionsCollection where
makeObject = makeObject . unHTMLOptionsCollection
instance IsHTMLCollection HTMLOptionsCollection
instance IsGObject HTMLOptionsCollection where
typeGType _ = gTypeHTMLOptionsCollection
{-# INLINE typeGType #-}
noHTMLOptionsCollection :: Maybe HTMLOptionsCollection
noHTMLOptionsCollection = Nothing
{-# INLINE noHTMLOptionsCollection #-}
gTypeHTMLOptionsCollection :: JSM GType
gTypeHTMLOptionsCollection = GType . Object <$> jsg "HTMLOptionsCollection"
newtype HTMLOutputElement = HTMLOutputElement { unHTMLOutputElement :: JSVal }
instance PToJSVal HTMLOutputElement where
pToJSVal = unHTMLOutputElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLOutputElement where
pFromJSVal = HTMLOutputElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLOutputElement where
toJSVal = return . unHTMLOutputElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLOutputElement where
fromJSVal v = fmap HTMLOutputElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLOutputElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLOutputElement where
makeObject = makeObject . unHTMLOutputElement
instance IsHTMLElement HTMLOutputElement
instance IsElement HTMLOutputElement
instance IsNode HTMLOutputElement
instance IsEventTarget HTMLOutputElement
instance IsSlotable HTMLOutputElement
instance IsParentNode HTMLOutputElement
instance IsNonDocumentTypeChildNode HTMLOutputElement
instance IsDocumentAndElementEventHandlers HTMLOutputElement
instance IsChildNode HTMLOutputElement
instance IsAnimatable HTMLOutputElement
instance IsGlobalEventHandlers HTMLOutputElement
instance IsElementCSSInlineStyle HTMLOutputElement
instance IsGObject HTMLOutputElement where
typeGType _ = gTypeHTMLOutputElement
{-# INLINE typeGType #-}
noHTMLOutputElement :: Maybe HTMLOutputElement
noHTMLOutputElement = Nothing
{-# INLINE noHTMLOutputElement #-}
gTypeHTMLOutputElement :: JSM GType
gTypeHTMLOutputElement = GType . Object <$> jsg "HTMLOutputElement"
newtype HTMLParagraphElement = HTMLParagraphElement { unHTMLParagraphElement :: JSVal }
instance PToJSVal HTMLParagraphElement where
pToJSVal = unHTMLParagraphElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLParagraphElement where
pFromJSVal = HTMLParagraphElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLParagraphElement where
toJSVal = return . unHTMLParagraphElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLParagraphElement where
fromJSVal v = fmap HTMLParagraphElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLParagraphElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLParagraphElement where
makeObject = makeObject . unHTMLParagraphElement
instance IsHTMLElement HTMLParagraphElement
instance IsElement HTMLParagraphElement
instance IsNode HTMLParagraphElement
instance IsEventTarget HTMLParagraphElement
instance IsSlotable HTMLParagraphElement
instance IsParentNode HTMLParagraphElement
instance IsNonDocumentTypeChildNode HTMLParagraphElement
instance IsDocumentAndElementEventHandlers HTMLParagraphElement
instance IsChildNode HTMLParagraphElement
instance IsAnimatable HTMLParagraphElement
instance IsGlobalEventHandlers HTMLParagraphElement
instance IsElementCSSInlineStyle HTMLParagraphElement
instance IsGObject HTMLParagraphElement where
typeGType _ = gTypeHTMLParagraphElement
{-# INLINE typeGType #-}
noHTMLParagraphElement :: Maybe HTMLParagraphElement
noHTMLParagraphElement = Nothing
{-# INLINE noHTMLParagraphElement #-}
gTypeHTMLParagraphElement :: JSM GType
gTypeHTMLParagraphElement = GType . Object <$> jsg "HTMLParagraphElement"
newtype HTMLParamElement = HTMLParamElement { unHTMLParamElement :: JSVal }
instance PToJSVal HTMLParamElement where
pToJSVal = unHTMLParamElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLParamElement where
pFromJSVal = HTMLParamElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLParamElement where
toJSVal = return . unHTMLParamElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLParamElement where
fromJSVal v = fmap HTMLParamElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLParamElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLParamElement where
makeObject = makeObject . unHTMLParamElement
instance IsHTMLElement HTMLParamElement
instance IsElement HTMLParamElement
instance IsNode HTMLParamElement
instance IsEventTarget HTMLParamElement
instance IsSlotable HTMLParamElement
instance IsParentNode HTMLParamElement
instance IsNonDocumentTypeChildNode HTMLParamElement
instance IsDocumentAndElementEventHandlers HTMLParamElement
instance IsChildNode HTMLParamElement
instance IsAnimatable HTMLParamElement
instance IsGlobalEventHandlers HTMLParamElement
instance IsElementCSSInlineStyle HTMLParamElement
instance IsGObject HTMLParamElement where
typeGType _ = gTypeHTMLParamElement
{-# INLINE typeGType #-}
noHTMLParamElement :: Maybe HTMLParamElement
noHTMLParamElement = Nothing
{-# INLINE noHTMLParamElement #-}
gTypeHTMLParamElement :: JSM GType
gTypeHTMLParamElement = GType . Object <$> jsg "HTMLParamElement"
newtype HTMLPictureElement = HTMLPictureElement { unHTMLPictureElement :: JSVal }
instance PToJSVal HTMLPictureElement where
pToJSVal = unHTMLPictureElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLPictureElement where
pFromJSVal = HTMLPictureElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLPictureElement where
toJSVal = return . unHTMLPictureElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLPictureElement where
fromJSVal v = fmap HTMLPictureElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLPictureElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLPictureElement where
makeObject = makeObject . unHTMLPictureElement
instance IsHTMLElement HTMLPictureElement
instance IsElement HTMLPictureElement
instance IsNode HTMLPictureElement
instance IsEventTarget HTMLPictureElement
instance IsSlotable HTMLPictureElement
instance IsParentNode HTMLPictureElement
instance IsNonDocumentTypeChildNode HTMLPictureElement
instance IsDocumentAndElementEventHandlers HTMLPictureElement
instance IsChildNode HTMLPictureElement
instance IsAnimatable HTMLPictureElement
instance IsGlobalEventHandlers HTMLPictureElement
instance IsElementCSSInlineStyle HTMLPictureElement
instance IsGObject HTMLPictureElement where
typeGType _ = gTypeHTMLPictureElement
{-# INLINE typeGType #-}
noHTMLPictureElement :: Maybe HTMLPictureElement
noHTMLPictureElement = Nothing
{-# INLINE noHTMLPictureElement #-}
gTypeHTMLPictureElement :: JSM GType
gTypeHTMLPictureElement = GType . Object <$> jsg "HTMLPictureElement"
newtype HTMLPreElement = HTMLPreElement { unHTMLPreElement :: JSVal }
instance PToJSVal HTMLPreElement where
pToJSVal = unHTMLPreElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLPreElement where
pFromJSVal = HTMLPreElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLPreElement where
toJSVal = return . unHTMLPreElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLPreElement where
fromJSVal v = fmap HTMLPreElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLPreElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLPreElement where
makeObject = makeObject . unHTMLPreElement
instance IsHTMLElement HTMLPreElement
instance IsElement HTMLPreElement
instance IsNode HTMLPreElement
instance IsEventTarget HTMLPreElement
instance IsSlotable HTMLPreElement
instance IsParentNode HTMLPreElement
instance IsNonDocumentTypeChildNode HTMLPreElement
instance IsDocumentAndElementEventHandlers HTMLPreElement
instance IsChildNode HTMLPreElement
instance IsAnimatable HTMLPreElement
instance IsGlobalEventHandlers HTMLPreElement
instance IsElementCSSInlineStyle HTMLPreElement
instance IsGObject HTMLPreElement where
typeGType _ = gTypeHTMLPreElement
{-# INLINE typeGType #-}
noHTMLPreElement :: Maybe HTMLPreElement
noHTMLPreElement = Nothing
{-# INLINE noHTMLPreElement #-}
gTypeHTMLPreElement :: JSM GType
gTypeHTMLPreElement = GType . Object <$> jsg "HTMLPreElement"
newtype HTMLProgressElement = HTMLProgressElement { unHTMLProgressElement :: JSVal }
instance PToJSVal HTMLProgressElement where
pToJSVal = unHTMLProgressElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLProgressElement where
pFromJSVal = HTMLProgressElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLProgressElement where
toJSVal = return . unHTMLProgressElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLProgressElement where
fromJSVal v = fmap HTMLProgressElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLProgressElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLProgressElement where
makeObject = makeObject . unHTMLProgressElement
instance IsHTMLElement HTMLProgressElement
instance IsElement HTMLProgressElement
instance IsNode HTMLProgressElement
instance IsEventTarget HTMLProgressElement
instance IsSlotable HTMLProgressElement
instance IsParentNode HTMLProgressElement
instance IsNonDocumentTypeChildNode HTMLProgressElement
instance IsDocumentAndElementEventHandlers HTMLProgressElement
instance IsChildNode HTMLProgressElement
instance IsAnimatable HTMLProgressElement
instance IsGlobalEventHandlers HTMLProgressElement
instance IsElementCSSInlineStyle HTMLProgressElement
instance IsGObject HTMLProgressElement where
typeGType _ = gTypeHTMLProgressElement
{-# INLINE typeGType #-}
noHTMLProgressElement :: Maybe HTMLProgressElement
noHTMLProgressElement = Nothing
{-# INLINE noHTMLProgressElement #-}
gTypeHTMLProgressElement :: JSM GType
gTypeHTMLProgressElement = GType . Object <$> jsg "HTMLProgressElement"
newtype HTMLQuoteElement = HTMLQuoteElement { unHTMLQuoteElement :: JSVal }
instance PToJSVal HTMLQuoteElement where
pToJSVal = unHTMLQuoteElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLQuoteElement where
pFromJSVal = HTMLQuoteElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLQuoteElement where
toJSVal = return . unHTMLQuoteElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLQuoteElement where
fromJSVal v = fmap HTMLQuoteElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLQuoteElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLQuoteElement where
makeObject = makeObject . unHTMLQuoteElement
instance IsHTMLElement HTMLQuoteElement
instance IsElement HTMLQuoteElement
instance IsNode HTMLQuoteElement
instance IsEventTarget HTMLQuoteElement
instance IsSlotable HTMLQuoteElement
instance IsParentNode HTMLQuoteElement
instance IsNonDocumentTypeChildNode HTMLQuoteElement
instance IsDocumentAndElementEventHandlers HTMLQuoteElement
instance IsChildNode HTMLQuoteElement
instance IsAnimatable HTMLQuoteElement
instance IsGlobalEventHandlers HTMLQuoteElement
instance IsElementCSSInlineStyle HTMLQuoteElement
instance IsGObject HTMLQuoteElement where
typeGType _ = gTypeHTMLQuoteElement
{-# INLINE typeGType #-}
noHTMLQuoteElement :: Maybe HTMLQuoteElement
noHTMLQuoteElement = Nothing
{-# INLINE noHTMLQuoteElement #-}
gTypeHTMLQuoteElement :: JSM GType
gTypeHTMLQuoteElement = GType . Object <$> jsg "HTMLQuoteElement"
newtype HTMLScriptElement = HTMLScriptElement { unHTMLScriptElement :: JSVal }
instance PToJSVal HTMLScriptElement where
pToJSVal = unHTMLScriptElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLScriptElement where
pFromJSVal = HTMLScriptElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLScriptElement where
toJSVal = return . unHTMLScriptElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLScriptElement where
fromJSVal v = fmap HTMLScriptElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLScriptElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLScriptElement where
makeObject = makeObject . unHTMLScriptElement
instance IsHTMLElement HTMLScriptElement
instance IsElement HTMLScriptElement
instance IsNode HTMLScriptElement
instance IsEventTarget HTMLScriptElement
instance IsSlotable HTMLScriptElement
instance IsParentNode HTMLScriptElement
instance IsNonDocumentTypeChildNode HTMLScriptElement
instance IsDocumentAndElementEventHandlers HTMLScriptElement
instance IsChildNode HTMLScriptElement
instance IsAnimatable HTMLScriptElement
instance IsGlobalEventHandlers HTMLScriptElement
instance IsElementCSSInlineStyle HTMLScriptElement
instance IsGObject HTMLScriptElement where
typeGType _ = gTypeHTMLScriptElement
{-# INLINE typeGType #-}
noHTMLScriptElement :: Maybe HTMLScriptElement
noHTMLScriptElement = Nothing
{-# INLINE noHTMLScriptElement #-}
gTypeHTMLScriptElement :: JSM GType
gTypeHTMLScriptElement = GType . Object <$> jsg "HTMLScriptElement"
newtype HTMLSelectElement = HTMLSelectElement { unHTMLSelectElement :: JSVal }
instance PToJSVal HTMLSelectElement where
pToJSVal = unHTMLSelectElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLSelectElement where
pFromJSVal = HTMLSelectElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLSelectElement where
toJSVal = return . unHTMLSelectElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLSelectElement where
fromJSVal v = fmap HTMLSelectElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLSelectElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLSelectElement where
makeObject = makeObject . unHTMLSelectElement
instance IsHTMLElement HTMLSelectElement
instance IsElement HTMLSelectElement
instance IsNode HTMLSelectElement
instance IsEventTarget HTMLSelectElement
instance IsSlotable HTMLSelectElement
instance IsParentNode HTMLSelectElement
instance IsNonDocumentTypeChildNode HTMLSelectElement
instance IsDocumentAndElementEventHandlers HTMLSelectElement
instance IsChildNode HTMLSelectElement
instance IsAnimatable HTMLSelectElement
instance IsGlobalEventHandlers HTMLSelectElement
instance IsElementCSSInlineStyle HTMLSelectElement
instance IsGObject HTMLSelectElement where
typeGType _ = gTypeHTMLSelectElement
{-# INLINE typeGType #-}
noHTMLSelectElement :: Maybe HTMLSelectElement
noHTMLSelectElement = Nothing
{-# INLINE noHTMLSelectElement #-}
gTypeHTMLSelectElement :: JSM GType
gTypeHTMLSelectElement = GType . Object <$> jsg "HTMLSelectElement"
newtype HTMLSlotElement = HTMLSlotElement { unHTMLSlotElement :: JSVal }
instance PToJSVal HTMLSlotElement where
pToJSVal = unHTMLSlotElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLSlotElement where
pFromJSVal = HTMLSlotElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLSlotElement where
toJSVal = return . unHTMLSlotElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLSlotElement where
fromJSVal v = fmap HTMLSlotElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLSlotElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLSlotElement where
makeObject = makeObject . unHTMLSlotElement
instance IsHTMLElement HTMLSlotElement
instance IsElement HTMLSlotElement
instance IsNode HTMLSlotElement
instance IsEventTarget HTMLSlotElement
instance IsSlotable HTMLSlotElement
instance IsParentNode HTMLSlotElement
instance IsNonDocumentTypeChildNode HTMLSlotElement
instance IsDocumentAndElementEventHandlers HTMLSlotElement
instance IsChildNode HTMLSlotElement
instance IsAnimatable HTMLSlotElement
instance IsGlobalEventHandlers HTMLSlotElement
instance IsElementCSSInlineStyle HTMLSlotElement
instance IsGObject HTMLSlotElement where
typeGType _ = gTypeHTMLSlotElement
{-# INLINE typeGType #-}
noHTMLSlotElement :: Maybe HTMLSlotElement
noHTMLSlotElement = Nothing
{-# INLINE noHTMLSlotElement #-}
gTypeHTMLSlotElement :: JSM GType
gTypeHTMLSlotElement = GType . Object <$> jsg "HTMLSlotElement"
newtype HTMLSourceElement = HTMLSourceElement { unHTMLSourceElement :: JSVal }
instance PToJSVal HTMLSourceElement where
pToJSVal = unHTMLSourceElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLSourceElement where
pFromJSVal = HTMLSourceElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLSourceElement where
toJSVal = return . unHTMLSourceElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLSourceElement where
fromJSVal v = fmap HTMLSourceElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLSourceElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLSourceElement where
makeObject = makeObject . unHTMLSourceElement
instance IsHTMLElement HTMLSourceElement
instance IsElement HTMLSourceElement
instance IsNode HTMLSourceElement
instance IsEventTarget HTMLSourceElement
instance IsSlotable HTMLSourceElement
instance IsParentNode HTMLSourceElement
instance IsNonDocumentTypeChildNode HTMLSourceElement
instance IsDocumentAndElementEventHandlers HTMLSourceElement
instance IsChildNode HTMLSourceElement
instance IsAnimatable HTMLSourceElement
instance IsGlobalEventHandlers HTMLSourceElement
instance IsElementCSSInlineStyle HTMLSourceElement
instance IsGObject HTMLSourceElement where
typeGType _ = gTypeHTMLSourceElement
{-# INLINE typeGType #-}
noHTMLSourceElement :: Maybe HTMLSourceElement
noHTMLSourceElement = Nothing
{-# INLINE noHTMLSourceElement #-}
gTypeHTMLSourceElement :: JSM GType
gTypeHTMLSourceElement = GType . Object <$> jsg "HTMLSourceElement"
newtype HTMLSpanElement = HTMLSpanElement { unHTMLSpanElement :: JSVal }
instance PToJSVal HTMLSpanElement where
pToJSVal = unHTMLSpanElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLSpanElement where
pFromJSVal = HTMLSpanElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLSpanElement where
toJSVal = return . unHTMLSpanElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLSpanElement where
fromJSVal v = fmap HTMLSpanElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLSpanElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLSpanElement where
makeObject = makeObject . unHTMLSpanElement
instance IsHTMLElement HTMLSpanElement
instance IsElement HTMLSpanElement
instance IsNode HTMLSpanElement
instance IsEventTarget HTMLSpanElement
instance IsSlotable HTMLSpanElement
instance IsParentNode HTMLSpanElement
instance IsNonDocumentTypeChildNode HTMLSpanElement
instance IsDocumentAndElementEventHandlers HTMLSpanElement
instance IsChildNode HTMLSpanElement
instance IsAnimatable HTMLSpanElement
instance IsGlobalEventHandlers HTMLSpanElement
instance IsElementCSSInlineStyle HTMLSpanElement
instance IsGObject HTMLSpanElement where
typeGType _ = gTypeHTMLSpanElement
{-# INLINE typeGType #-}
noHTMLSpanElement :: Maybe HTMLSpanElement
noHTMLSpanElement = Nothing
{-# INLINE noHTMLSpanElement #-}
gTypeHTMLSpanElement :: JSM GType
gTypeHTMLSpanElement = GType . Object <$> jsg "HTMLSpanElement"
newtype HTMLStyleElement = HTMLStyleElement { unHTMLStyleElement :: JSVal }
instance PToJSVal HTMLStyleElement where
pToJSVal = unHTMLStyleElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLStyleElement where
pFromJSVal = HTMLStyleElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLStyleElement where
toJSVal = return . unHTMLStyleElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLStyleElement where
fromJSVal v = fmap HTMLStyleElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLStyleElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLStyleElement where
makeObject = makeObject . unHTMLStyleElement
instance IsHTMLElement HTMLStyleElement
instance IsElement HTMLStyleElement
instance IsNode HTMLStyleElement
instance IsEventTarget HTMLStyleElement
instance IsSlotable HTMLStyleElement
instance IsParentNode HTMLStyleElement
instance IsNonDocumentTypeChildNode HTMLStyleElement
instance IsDocumentAndElementEventHandlers HTMLStyleElement
instance IsChildNode HTMLStyleElement
instance IsAnimatable HTMLStyleElement
instance IsGlobalEventHandlers HTMLStyleElement
instance IsElementCSSInlineStyle HTMLStyleElement
instance IsGObject HTMLStyleElement where
typeGType _ = gTypeHTMLStyleElement
{-# INLINE typeGType #-}
noHTMLStyleElement :: Maybe HTMLStyleElement
noHTMLStyleElement = Nothing
{-# INLINE noHTMLStyleElement #-}
gTypeHTMLStyleElement :: JSM GType
gTypeHTMLStyleElement = GType . Object <$> jsg "HTMLStyleElement"
newtype HTMLTableCaptionElement = HTMLTableCaptionElement { unHTMLTableCaptionElement :: JSVal }
instance PToJSVal HTMLTableCaptionElement where
pToJSVal = unHTMLTableCaptionElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLTableCaptionElement where
pFromJSVal = HTMLTableCaptionElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLTableCaptionElement where
toJSVal = return . unHTMLTableCaptionElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLTableCaptionElement where
fromJSVal v = fmap HTMLTableCaptionElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLTableCaptionElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLTableCaptionElement where
makeObject = makeObject . unHTMLTableCaptionElement
instance IsHTMLElement HTMLTableCaptionElement
instance IsElement HTMLTableCaptionElement
instance IsNode HTMLTableCaptionElement
instance IsEventTarget HTMLTableCaptionElement
instance IsSlotable HTMLTableCaptionElement
instance IsParentNode HTMLTableCaptionElement
instance IsNonDocumentTypeChildNode HTMLTableCaptionElement
instance IsDocumentAndElementEventHandlers HTMLTableCaptionElement
instance IsChildNode HTMLTableCaptionElement
instance IsAnimatable HTMLTableCaptionElement
instance IsGlobalEventHandlers HTMLTableCaptionElement
instance IsElementCSSInlineStyle HTMLTableCaptionElement
instance IsGObject HTMLTableCaptionElement where
typeGType _ = gTypeHTMLTableCaptionElement
{-# INLINE typeGType #-}
noHTMLTableCaptionElement :: Maybe HTMLTableCaptionElement
noHTMLTableCaptionElement = Nothing
{-# INLINE noHTMLTableCaptionElement #-}
gTypeHTMLTableCaptionElement :: JSM GType
gTypeHTMLTableCaptionElement = GType . Object <$> jsg "HTMLTableCaptionElement"
newtype HTMLTableCellElement = HTMLTableCellElement { unHTMLTableCellElement :: JSVal }
instance PToJSVal HTMLTableCellElement where
pToJSVal = unHTMLTableCellElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLTableCellElement where
pFromJSVal = HTMLTableCellElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLTableCellElement where
toJSVal = return . unHTMLTableCellElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLTableCellElement where
fromJSVal v = fmap HTMLTableCellElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLTableCellElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLTableCellElement where
makeObject = makeObject . unHTMLTableCellElement
instance IsHTMLElement HTMLTableCellElement
instance IsElement HTMLTableCellElement
instance IsNode HTMLTableCellElement
instance IsEventTarget HTMLTableCellElement
instance IsSlotable HTMLTableCellElement
instance IsParentNode HTMLTableCellElement
instance IsNonDocumentTypeChildNode HTMLTableCellElement
instance IsDocumentAndElementEventHandlers HTMLTableCellElement
instance IsChildNode HTMLTableCellElement
instance IsAnimatable HTMLTableCellElement
instance IsGlobalEventHandlers HTMLTableCellElement
instance IsElementCSSInlineStyle HTMLTableCellElement
instance IsGObject HTMLTableCellElement where
typeGType _ = gTypeHTMLTableCellElement
{-# INLINE typeGType #-}
noHTMLTableCellElement :: Maybe HTMLTableCellElement
noHTMLTableCellElement = Nothing
{-# INLINE noHTMLTableCellElement #-}
gTypeHTMLTableCellElement :: JSM GType
gTypeHTMLTableCellElement = GType . Object <$> jsg "HTMLTableCellElement"
newtype HTMLTableColElement = HTMLTableColElement { unHTMLTableColElement :: JSVal }
instance PToJSVal HTMLTableColElement where
pToJSVal = unHTMLTableColElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLTableColElement where
pFromJSVal = HTMLTableColElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLTableColElement where
toJSVal = return . unHTMLTableColElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLTableColElement where
fromJSVal v = fmap HTMLTableColElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLTableColElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLTableColElement where
makeObject = makeObject . unHTMLTableColElement
instance IsHTMLElement HTMLTableColElement
instance IsElement HTMLTableColElement
instance IsNode HTMLTableColElement
instance IsEventTarget HTMLTableColElement
instance IsSlotable HTMLTableColElement
instance IsParentNode HTMLTableColElement
instance IsNonDocumentTypeChildNode HTMLTableColElement
instance IsDocumentAndElementEventHandlers HTMLTableColElement
instance IsChildNode HTMLTableColElement
instance IsAnimatable HTMLTableColElement
instance IsGlobalEventHandlers HTMLTableColElement
instance IsElementCSSInlineStyle HTMLTableColElement
instance IsGObject HTMLTableColElement where
typeGType _ = gTypeHTMLTableColElement
{-# INLINE typeGType #-}
noHTMLTableColElement :: Maybe HTMLTableColElement
noHTMLTableColElement = Nothing
{-# INLINE noHTMLTableColElement #-}
gTypeHTMLTableColElement :: JSM GType
gTypeHTMLTableColElement = GType . Object <$> jsg "HTMLTableColElement"
newtype HTMLTableElement = HTMLTableElement { unHTMLTableElement :: JSVal }
instance PToJSVal HTMLTableElement where
pToJSVal = unHTMLTableElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLTableElement where
pFromJSVal = HTMLTableElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLTableElement where
toJSVal = return . unHTMLTableElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLTableElement where
fromJSVal v = fmap HTMLTableElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLTableElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLTableElement where
makeObject = makeObject . unHTMLTableElement
instance IsHTMLElement HTMLTableElement
instance IsElement HTMLTableElement
instance IsNode HTMLTableElement
instance IsEventTarget HTMLTableElement
instance IsSlotable HTMLTableElement
instance IsParentNode HTMLTableElement
instance IsNonDocumentTypeChildNode HTMLTableElement
instance IsDocumentAndElementEventHandlers HTMLTableElement
instance IsChildNode HTMLTableElement
instance IsAnimatable HTMLTableElement
instance IsGlobalEventHandlers HTMLTableElement
instance IsElementCSSInlineStyle HTMLTableElement
instance IsGObject HTMLTableElement where
typeGType _ = gTypeHTMLTableElement
{-# INLINE typeGType #-}
noHTMLTableElement :: Maybe HTMLTableElement
noHTMLTableElement = Nothing
{-# INLINE noHTMLTableElement #-}
gTypeHTMLTableElement :: JSM GType
gTypeHTMLTableElement = GType . Object <$> jsg "HTMLTableElement"
newtype HTMLTableRowElement = HTMLTableRowElement { unHTMLTableRowElement :: JSVal }
instance PToJSVal HTMLTableRowElement where
pToJSVal = unHTMLTableRowElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLTableRowElement where
pFromJSVal = HTMLTableRowElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLTableRowElement where
toJSVal = return . unHTMLTableRowElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLTableRowElement where
fromJSVal v = fmap HTMLTableRowElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLTableRowElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLTableRowElement where
makeObject = makeObject . unHTMLTableRowElement
instance IsHTMLElement HTMLTableRowElement
instance IsElement HTMLTableRowElement
instance IsNode HTMLTableRowElement
instance IsEventTarget HTMLTableRowElement
instance IsSlotable HTMLTableRowElement
instance IsParentNode HTMLTableRowElement
instance IsNonDocumentTypeChildNode HTMLTableRowElement
instance IsDocumentAndElementEventHandlers HTMLTableRowElement
instance IsChildNode HTMLTableRowElement
instance IsAnimatable HTMLTableRowElement
instance IsGlobalEventHandlers HTMLTableRowElement
instance IsElementCSSInlineStyle HTMLTableRowElement
instance IsGObject HTMLTableRowElement where
typeGType _ = gTypeHTMLTableRowElement
{-# INLINE typeGType #-}
noHTMLTableRowElement :: Maybe HTMLTableRowElement
noHTMLTableRowElement = Nothing
{-# INLINE noHTMLTableRowElement #-}
gTypeHTMLTableRowElement :: JSM GType
gTypeHTMLTableRowElement = GType . Object <$> jsg "HTMLTableRowElement"
newtype HTMLTableSectionElement = HTMLTableSectionElement { unHTMLTableSectionElement :: JSVal }
instance PToJSVal HTMLTableSectionElement where
pToJSVal = unHTMLTableSectionElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLTableSectionElement where
pFromJSVal = HTMLTableSectionElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLTableSectionElement where
toJSVal = return . unHTMLTableSectionElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLTableSectionElement where
fromJSVal v = fmap HTMLTableSectionElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLTableSectionElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLTableSectionElement where
makeObject = makeObject . unHTMLTableSectionElement
instance IsHTMLElement HTMLTableSectionElement
instance IsElement HTMLTableSectionElement
instance IsNode HTMLTableSectionElement
instance IsEventTarget HTMLTableSectionElement
instance IsSlotable HTMLTableSectionElement
instance IsParentNode HTMLTableSectionElement
instance IsNonDocumentTypeChildNode HTMLTableSectionElement
instance IsDocumentAndElementEventHandlers HTMLTableSectionElement
instance IsChildNode HTMLTableSectionElement
instance IsAnimatable HTMLTableSectionElement
instance IsGlobalEventHandlers HTMLTableSectionElement
instance IsElementCSSInlineStyle HTMLTableSectionElement
instance IsGObject HTMLTableSectionElement where
typeGType _ = gTypeHTMLTableSectionElement
{-# INLINE typeGType #-}
noHTMLTableSectionElement :: Maybe HTMLTableSectionElement
noHTMLTableSectionElement = Nothing
{-# INLINE noHTMLTableSectionElement #-}
gTypeHTMLTableSectionElement :: JSM GType
gTypeHTMLTableSectionElement = GType . Object <$> jsg "HTMLTableSectionElement"
newtype HTMLTemplateElement = HTMLTemplateElement { unHTMLTemplateElement :: JSVal }
instance PToJSVal HTMLTemplateElement where
pToJSVal = unHTMLTemplateElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLTemplateElement where
pFromJSVal = HTMLTemplateElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLTemplateElement where
toJSVal = return . unHTMLTemplateElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLTemplateElement where
fromJSVal v = fmap HTMLTemplateElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLTemplateElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLTemplateElement where
makeObject = makeObject . unHTMLTemplateElement
instance IsHTMLElement HTMLTemplateElement
instance IsElement HTMLTemplateElement
instance IsNode HTMLTemplateElement
instance IsEventTarget HTMLTemplateElement
instance IsSlotable HTMLTemplateElement
instance IsParentNode HTMLTemplateElement
instance IsNonDocumentTypeChildNode HTMLTemplateElement
instance IsDocumentAndElementEventHandlers HTMLTemplateElement
instance IsChildNode HTMLTemplateElement
instance IsAnimatable HTMLTemplateElement
instance IsGlobalEventHandlers HTMLTemplateElement
instance IsElementCSSInlineStyle HTMLTemplateElement
instance IsGObject HTMLTemplateElement where
typeGType _ = gTypeHTMLTemplateElement
{-# INLINE typeGType #-}
noHTMLTemplateElement :: Maybe HTMLTemplateElement
noHTMLTemplateElement = Nothing
{-# INLINE noHTMLTemplateElement #-}
gTypeHTMLTemplateElement :: JSM GType
gTypeHTMLTemplateElement = GType . Object <$> jsg "HTMLTemplateElement"
newtype HTMLTextAreaElement = HTMLTextAreaElement { unHTMLTextAreaElement :: JSVal }
instance PToJSVal HTMLTextAreaElement where
pToJSVal = unHTMLTextAreaElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLTextAreaElement where
pFromJSVal = HTMLTextAreaElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLTextAreaElement where
toJSVal = return . unHTMLTextAreaElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLTextAreaElement where
fromJSVal v = fmap HTMLTextAreaElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLTextAreaElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLTextAreaElement where
makeObject = makeObject . unHTMLTextAreaElement
instance IsHTMLElement HTMLTextAreaElement
instance IsElement HTMLTextAreaElement
instance IsNode HTMLTextAreaElement
instance IsEventTarget HTMLTextAreaElement
instance IsSlotable HTMLTextAreaElement
instance IsParentNode HTMLTextAreaElement
instance IsNonDocumentTypeChildNode HTMLTextAreaElement
instance IsDocumentAndElementEventHandlers HTMLTextAreaElement
instance IsChildNode HTMLTextAreaElement
instance IsAnimatable HTMLTextAreaElement
instance IsGlobalEventHandlers HTMLTextAreaElement
instance IsElementCSSInlineStyle HTMLTextAreaElement
instance IsGObject HTMLTextAreaElement where
typeGType _ = gTypeHTMLTextAreaElement
{-# INLINE typeGType #-}
noHTMLTextAreaElement :: Maybe HTMLTextAreaElement
noHTMLTextAreaElement = Nothing
{-# INLINE noHTMLTextAreaElement #-}
gTypeHTMLTextAreaElement :: JSM GType
gTypeHTMLTextAreaElement = GType . Object <$> jsg "HTMLTextAreaElement"
newtype HTMLTimeElement = HTMLTimeElement { unHTMLTimeElement :: JSVal }
instance PToJSVal HTMLTimeElement where
pToJSVal = unHTMLTimeElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLTimeElement where
pFromJSVal = HTMLTimeElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLTimeElement where
toJSVal = return . unHTMLTimeElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLTimeElement where
fromJSVal v = fmap HTMLTimeElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLTimeElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLTimeElement where
makeObject = makeObject . unHTMLTimeElement
instance IsHTMLElement HTMLTimeElement
instance IsElement HTMLTimeElement
instance IsNode HTMLTimeElement
instance IsEventTarget HTMLTimeElement
instance IsSlotable HTMLTimeElement
instance IsParentNode HTMLTimeElement
instance IsNonDocumentTypeChildNode HTMLTimeElement
instance IsDocumentAndElementEventHandlers HTMLTimeElement
instance IsChildNode HTMLTimeElement
instance IsAnimatable HTMLTimeElement
instance IsGlobalEventHandlers HTMLTimeElement
instance IsElementCSSInlineStyle HTMLTimeElement
instance IsGObject HTMLTimeElement where
typeGType _ = gTypeHTMLTimeElement
{-# INLINE typeGType #-}
noHTMLTimeElement :: Maybe HTMLTimeElement
noHTMLTimeElement = Nothing
{-# INLINE noHTMLTimeElement #-}
gTypeHTMLTimeElement :: JSM GType
gTypeHTMLTimeElement = GType . Object <$> jsg "HTMLTimeElement"
newtype HTMLTitleElement = HTMLTitleElement { unHTMLTitleElement :: JSVal }
instance PToJSVal HTMLTitleElement where
pToJSVal = unHTMLTitleElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLTitleElement where
pFromJSVal = HTMLTitleElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLTitleElement where
toJSVal = return . unHTMLTitleElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLTitleElement where
fromJSVal v = fmap HTMLTitleElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLTitleElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLTitleElement where
makeObject = makeObject . unHTMLTitleElement
instance IsHTMLElement HTMLTitleElement
instance IsElement HTMLTitleElement
instance IsNode HTMLTitleElement
instance IsEventTarget HTMLTitleElement
instance IsSlotable HTMLTitleElement
instance IsParentNode HTMLTitleElement
instance IsNonDocumentTypeChildNode HTMLTitleElement
instance IsDocumentAndElementEventHandlers HTMLTitleElement
instance IsChildNode HTMLTitleElement
instance IsAnimatable HTMLTitleElement
instance IsGlobalEventHandlers HTMLTitleElement
instance IsElementCSSInlineStyle HTMLTitleElement
instance IsGObject HTMLTitleElement where
typeGType _ = gTypeHTMLTitleElement
{-# INLINE typeGType #-}
noHTMLTitleElement :: Maybe HTMLTitleElement
noHTMLTitleElement = Nothing
{-# INLINE noHTMLTitleElement #-}
gTypeHTMLTitleElement :: JSM GType
gTypeHTMLTitleElement = GType . Object <$> jsg "HTMLTitleElement"
newtype HTMLTrackElement = HTMLTrackElement { unHTMLTrackElement :: JSVal }
instance PToJSVal HTMLTrackElement where
pToJSVal = unHTMLTrackElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLTrackElement where
pFromJSVal = HTMLTrackElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLTrackElement where
toJSVal = return . unHTMLTrackElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLTrackElement where
fromJSVal v = fmap HTMLTrackElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLTrackElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLTrackElement where
makeObject = makeObject . unHTMLTrackElement
instance IsHTMLElement HTMLTrackElement
instance IsElement HTMLTrackElement
instance IsNode HTMLTrackElement
instance IsEventTarget HTMLTrackElement
instance IsSlotable HTMLTrackElement
instance IsParentNode HTMLTrackElement
instance IsNonDocumentTypeChildNode HTMLTrackElement
instance IsDocumentAndElementEventHandlers HTMLTrackElement
instance IsChildNode HTMLTrackElement
instance IsAnimatable HTMLTrackElement
instance IsGlobalEventHandlers HTMLTrackElement
instance IsElementCSSInlineStyle HTMLTrackElement
instance IsGObject HTMLTrackElement where
typeGType _ = gTypeHTMLTrackElement
{-# INLINE typeGType #-}
noHTMLTrackElement :: Maybe HTMLTrackElement
noHTMLTrackElement = Nothing
{-# INLINE noHTMLTrackElement #-}
gTypeHTMLTrackElement :: JSM GType
gTypeHTMLTrackElement = GType . Object <$> jsg "HTMLTrackElement"
newtype HTMLUListElement = HTMLUListElement { unHTMLUListElement :: JSVal }
instance PToJSVal HTMLUListElement where
pToJSVal = unHTMLUListElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLUListElement where
pFromJSVal = HTMLUListElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLUListElement where
toJSVal = return . unHTMLUListElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLUListElement where
fromJSVal v = fmap HTMLUListElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLUListElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLUListElement where
makeObject = makeObject . unHTMLUListElement
instance IsHTMLElement HTMLUListElement
instance IsElement HTMLUListElement
instance IsNode HTMLUListElement
instance IsEventTarget HTMLUListElement
instance IsSlotable HTMLUListElement
instance IsParentNode HTMLUListElement
instance IsNonDocumentTypeChildNode HTMLUListElement
instance IsDocumentAndElementEventHandlers HTMLUListElement
instance IsChildNode HTMLUListElement
instance IsAnimatable HTMLUListElement
instance IsGlobalEventHandlers HTMLUListElement
instance IsElementCSSInlineStyle HTMLUListElement
instance IsGObject HTMLUListElement where
typeGType _ = gTypeHTMLUListElement
{-# INLINE typeGType #-}
noHTMLUListElement :: Maybe HTMLUListElement
noHTMLUListElement = Nothing
{-# INLINE noHTMLUListElement #-}
gTypeHTMLUListElement :: JSM GType
gTypeHTMLUListElement = GType . Object <$> jsg "HTMLUListElement"
newtype HTMLUnknownElement = HTMLUnknownElement { unHTMLUnknownElement :: JSVal }
instance PToJSVal HTMLUnknownElement where
pToJSVal = unHTMLUnknownElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLUnknownElement where
pFromJSVal = HTMLUnknownElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLUnknownElement where
toJSVal = return . unHTMLUnknownElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLUnknownElement where
fromJSVal v = fmap HTMLUnknownElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLUnknownElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLUnknownElement where
makeObject = makeObject . unHTMLUnknownElement
instance IsHTMLElement HTMLUnknownElement
instance IsElement HTMLUnknownElement
instance IsNode HTMLUnknownElement
instance IsEventTarget HTMLUnknownElement
instance IsSlotable HTMLUnknownElement
instance IsParentNode HTMLUnknownElement
instance IsNonDocumentTypeChildNode HTMLUnknownElement
instance IsDocumentAndElementEventHandlers HTMLUnknownElement
instance IsChildNode HTMLUnknownElement
instance IsAnimatable HTMLUnknownElement
instance IsGlobalEventHandlers HTMLUnknownElement
instance IsElementCSSInlineStyle HTMLUnknownElement
instance IsGObject HTMLUnknownElement where
typeGType _ = gTypeHTMLUnknownElement
{-# INLINE typeGType #-}
noHTMLUnknownElement :: Maybe HTMLUnknownElement
noHTMLUnknownElement = Nothing
{-# INLINE noHTMLUnknownElement #-}
gTypeHTMLUnknownElement :: JSM GType
gTypeHTMLUnknownElement = GType . Object <$> jsg "HTMLUnknownElement"
newtype HTMLVideoElement = HTMLVideoElement { unHTMLVideoElement :: JSVal }
instance PToJSVal HTMLVideoElement where
pToJSVal = unHTMLVideoElement
{-# INLINE pToJSVal #-}
instance PFromJSVal HTMLVideoElement where
pFromJSVal = HTMLVideoElement
{-# INLINE pFromJSVal #-}
instance ToJSVal HTMLVideoElement where
toJSVal = return . unHTMLVideoElement
{-# INLINE toJSVal #-}
instance FromJSVal HTMLVideoElement where
fromJSVal v = fmap HTMLVideoElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HTMLVideoElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HTMLVideoElement where
makeObject = makeObject . unHTMLVideoElement
instance IsHTMLMediaElement HTMLVideoElement
instance IsHTMLElement HTMLVideoElement
instance IsElement HTMLVideoElement
instance IsNode HTMLVideoElement
instance IsEventTarget HTMLVideoElement
instance IsSlotable HTMLVideoElement
instance IsParentNode HTMLVideoElement
instance IsNonDocumentTypeChildNode HTMLVideoElement
instance IsDocumentAndElementEventHandlers HTMLVideoElement
instance IsChildNode HTMLVideoElement
instance IsAnimatable HTMLVideoElement
instance IsGlobalEventHandlers HTMLVideoElement
instance IsElementCSSInlineStyle HTMLVideoElement
instance IsGObject HTMLVideoElement where
typeGType _ = gTypeHTMLVideoElement
{-# INLINE typeGType #-}
noHTMLVideoElement :: Maybe HTMLVideoElement
noHTMLVideoElement = Nothing
{-# INLINE noHTMLVideoElement #-}
gTypeHTMLVideoElement :: JSM GType
gTypeHTMLVideoElement = GType . Object <$> jsg "HTMLVideoElement"
newtype HashChangeEvent = HashChangeEvent { unHashChangeEvent :: JSVal }
instance PToJSVal HashChangeEvent where
pToJSVal = unHashChangeEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal HashChangeEvent where
pFromJSVal = HashChangeEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal HashChangeEvent where
toJSVal = return . unHashChangeEvent
{-# INLINE toJSVal #-}
instance FromJSVal HashChangeEvent where
fromJSVal v = fmap HashChangeEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HashChangeEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HashChangeEvent where
makeObject = makeObject . unHashChangeEvent
instance IsEvent HashChangeEvent
instance IsGObject HashChangeEvent where
typeGType _ = gTypeHashChangeEvent
{-# INLINE typeGType #-}
noHashChangeEvent :: Maybe HashChangeEvent
noHashChangeEvent = Nothing
{-# INLINE noHashChangeEvent #-}
gTypeHashChangeEvent :: JSM GType
gTypeHashChangeEvent = GType . Object <$> jsg "HashChangeEvent"
newtype HashChangeEventInit = HashChangeEventInit { unHashChangeEventInit :: JSVal }
instance PToJSVal HashChangeEventInit where
pToJSVal = unHashChangeEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal HashChangeEventInit where
pFromJSVal = HashChangeEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal HashChangeEventInit where
toJSVal = return . unHashChangeEventInit
{-# INLINE toJSVal #-}
instance FromJSVal HashChangeEventInit where
fromJSVal v = fmap HashChangeEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HashChangeEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HashChangeEventInit where
makeObject = makeObject . unHashChangeEventInit
instance IsEventInit HashChangeEventInit
instance IsGObject HashChangeEventInit where
typeGType _ = gTypeHashChangeEventInit
{-# INLINE typeGType #-}
noHashChangeEventInit :: Maybe HashChangeEventInit
noHashChangeEventInit = Nothing
{-# INLINE noHashChangeEventInit #-}
gTypeHashChangeEventInit :: JSM GType
gTypeHashChangeEventInit = GType . Object <$> jsg "HashChangeEventInit"
newtype Headers = Headers { unHeaders :: JSVal }
instance PToJSVal Headers where
pToJSVal = unHeaders
{-# INLINE pToJSVal #-}
instance PFromJSVal Headers where
pFromJSVal = Headers
{-# INLINE pFromJSVal #-}
instance ToJSVal Headers where
toJSVal = return . unHeaders
{-# INLINE toJSVal #-}
instance FromJSVal Headers where
fromJSVal v = fmap Headers <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Headers
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Headers where
makeObject = makeObject . unHeaders
instance IsGObject Headers where
typeGType _ = gTypeHeaders
{-# INLINE typeGType #-}
noHeaders :: Maybe Headers
noHeaders = Nothing
{-# INLINE noHeaders #-}
gTypeHeaders :: JSM GType
gTypeHeaders = GType . Object <$> jsg "Headers"
newtype History = History { unHistory :: JSVal }
instance PToJSVal History where
pToJSVal = unHistory
{-# INLINE pToJSVal #-}
instance PFromJSVal History where
pFromJSVal = History
{-# INLINE pFromJSVal #-}
instance ToJSVal History where
toJSVal = return . unHistory
{-# INLINE toJSVal #-}
instance FromJSVal History where
fromJSVal v = fmap History <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . History
{-# INLINE fromJSValUnchecked #-}
instance MakeObject History where
makeObject = makeObject . unHistory
instance IsGObject History where
typeGType _ = gTypeHistory
{-# INLINE typeGType #-}
noHistory :: Maybe History
noHistory = Nothing
{-# INLINE noHistory #-}
gTypeHistory :: JSM GType
gTypeHistory = GType . Object <$> jsg "History"
newtype HkdfParams = HkdfParams { unHkdfParams :: JSVal }
instance PToJSVal HkdfParams where
pToJSVal = unHkdfParams
{-# INLINE pToJSVal #-}
instance PFromJSVal HkdfParams where
pFromJSVal = HkdfParams
{-# INLINE pFromJSVal #-}
instance ToJSVal HkdfParams where
toJSVal = return . unHkdfParams
{-# INLINE toJSVal #-}
instance FromJSVal HkdfParams where
fromJSVal v = fmap HkdfParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HkdfParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HkdfParams where
makeObject = makeObject . unHkdfParams
instance IsCryptoAlgorithmParameters HkdfParams
instance IsGObject HkdfParams where
typeGType _ = gTypeHkdfParams
{-# INLINE typeGType #-}
noHkdfParams :: Maybe HkdfParams
noHkdfParams = Nothing
{-# INLINE noHkdfParams #-}
gTypeHkdfParams :: JSM GType
gTypeHkdfParams = GType . Object <$> jsg "HkdfParams"
newtype HmacKeyParams = HmacKeyParams { unHmacKeyParams :: JSVal }
instance PToJSVal HmacKeyParams where
pToJSVal = unHmacKeyParams
{-# INLINE pToJSVal #-}
instance PFromJSVal HmacKeyParams where
pFromJSVal = HmacKeyParams
{-# INLINE pFromJSVal #-}
instance ToJSVal HmacKeyParams where
toJSVal = return . unHmacKeyParams
{-# INLINE toJSVal #-}
instance FromJSVal HmacKeyParams where
fromJSVal v = fmap HmacKeyParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . HmacKeyParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject HmacKeyParams where
makeObject = makeObject . unHmacKeyParams
instance IsCryptoAlgorithmParameters HmacKeyParams
instance IsGObject HmacKeyParams where
typeGType _ = gTypeHmacKeyParams
{-# INLINE typeGType #-}
noHmacKeyParams :: Maybe HmacKeyParams
noHmacKeyParams = Nothing
{-# INLINE noHmacKeyParams #-}
gTypeHmacKeyParams :: JSM GType
gTypeHmacKeyParams = GType . Object <$> jsg "HmacKeyParams"
newtype IDBCursor = IDBCursor { unIDBCursor :: JSVal }
instance PToJSVal IDBCursor where
pToJSVal = unIDBCursor
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBCursor where
pFromJSVal = IDBCursor
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBCursor where
toJSVal = return . unIDBCursor
{-# INLINE toJSVal #-}
instance FromJSVal IDBCursor where
fromJSVal v = fmap IDBCursor <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBCursor
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBCursor where
makeObject = makeObject . unIDBCursor
class (IsGObject o) => IsIDBCursor o
toIDBCursor :: IsIDBCursor o => o -> IDBCursor
toIDBCursor = IDBCursor . coerce
instance IsIDBCursor IDBCursor
instance IsGObject IDBCursor where
typeGType _ = gTypeIDBCursor
{-# INLINE typeGType #-}
noIDBCursor :: Maybe IDBCursor
noIDBCursor = Nothing
{-# INLINE noIDBCursor #-}
gTypeIDBCursor :: JSM GType
gTypeIDBCursor = GType . Object <$> jsg "IDBCursor"
newtype IDBCursorWithValue = IDBCursorWithValue { unIDBCursorWithValue :: JSVal }
instance PToJSVal IDBCursorWithValue where
pToJSVal = unIDBCursorWithValue
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBCursorWithValue where
pFromJSVal = IDBCursorWithValue
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBCursorWithValue where
toJSVal = return . unIDBCursorWithValue
{-# INLINE toJSVal #-}
instance FromJSVal IDBCursorWithValue where
fromJSVal v = fmap IDBCursorWithValue <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBCursorWithValue
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBCursorWithValue where
makeObject = makeObject . unIDBCursorWithValue
instance IsIDBCursor IDBCursorWithValue
instance IsGObject IDBCursorWithValue where
typeGType _ = gTypeIDBCursorWithValue
{-# INLINE typeGType #-}
noIDBCursorWithValue :: Maybe IDBCursorWithValue
noIDBCursorWithValue = Nothing
{-# INLINE noIDBCursorWithValue #-}
gTypeIDBCursorWithValue :: JSM GType
gTypeIDBCursorWithValue = GType . Object <$> jsg "IDBCursorWithValue"
newtype IDBDatabase = IDBDatabase { unIDBDatabase :: JSVal }
instance PToJSVal IDBDatabase where
pToJSVal = unIDBDatabase
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBDatabase where
pFromJSVal = IDBDatabase
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBDatabase where
toJSVal = return . unIDBDatabase
{-# INLINE toJSVal #-}
instance FromJSVal IDBDatabase where
fromJSVal v = fmap IDBDatabase <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBDatabase
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBDatabase where
makeObject = makeObject . unIDBDatabase
instance IsEventTarget IDBDatabase
instance IsGObject IDBDatabase where
typeGType _ = gTypeIDBDatabase
{-# INLINE typeGType #-}
noIDBDatabase :: Maybe IDBDatabase
noIDBDatabase = Nothing
{-# INLINE noIDBDatabase #-}
gTypeIDBDatabase :: JSM GType
gTypeIDBDatabase = GType . Object <$> jsg "IDBDatabase"
newtype IDBFactory = IDBFactory { unIDBFactory :: JSVal }
instance PToJSVal IDBFactory where
pToJSVal = unIDBFactory
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBFactory where
pFromJSVal = IDBFactory
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBFactory where
toJSVal = return . unIDBFactory
{-# INLINE toJSVal #-}
instance FromJSVal IDBFactory where
fromJSVal v = fmap IDBFactory <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBFactory
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBFactory where
makeObject = makeObject . unIDBFactory
instance IsGObject IDBFactory where
typeGType _ = gTypeIDBFactory
{-# INLINE typeGType #-}
noIDBFactory :: Maybe IDBFactory
noIDBFactory = Nothing
{-# INLINE noIDBFactory #-}
gTypeIDBFactory :: JSM GType
gTypeIDBFactory = GType . Object <$> jsg "IDBFactory"
newtype IDBIndex = IDBIndex { unIDBIndex :: JSVal }
instance PToJSVal IDBIndex where
pToJSVal = unIDBIndex
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBIndex where
pFromJSVal = IDBIndex
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBIndex where
toJSVal = return . unIDBIndex
{-# INLINE toJSVal #-}
instance FromJSVal IDBIndex where
fromJSVal v = fmap IDBIndex <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBIndex
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBIndex where
makeObject = makeObject . unIDBIndex
instance IsGObject IDBIndex where
typeGType _ = gTypeIDBIndex
{-# INLINE typeGType #-}
noIDBIndex :: Maybe IDBIndex
noIDBIndex = Nothing
{-# INLINE noIDBIndex #-}
gTypeIDBIndex :: JSM GType
gTypeIDBIndex = GType . Object <$> jsg "IDBIndex"
newtype IDBIndexParameters = IDBIndexParameters { unIDBIndexParameters :: JSVal }
instance PToJSVal IDBIndexParameters where
pToJSVal = unIDBIndexParameters
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBIndexParameters where
pFromJSVal = IDBIndexParameters
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBIndexParameters where
toJSVal = return . unIDBIndexParameters
{-# INLINE toJSVal #-}
instance FromJSVal IDBIndexParameters where
fromJSVal v = fmap IDBIndexParameters <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBIndexParameters
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBIndexParameters where
makeObject = makeObject . unIDBIndexParameters
instance IsGObject IDBIndexParameters where
typeGType _ = gTypeIDBIndexParameters
{-# INLINE typeGType #-}
noIDBIndexParameters :: Maybe IDBIndexParameters
noIDBIndexParameters = Nothing
{-# INLINE noIDBIndexParameters #-}
gTypeIDBIndexParameters :: JSM GType
gTypeIDBIndexParameters = GType . Object <$> jsg "IDBIndexParameters"
newtype IDBKeyRange = IDBKeyRange { unIDBKeyRange :: JSVal }
instance PToJSVal IDBKeyRange where
pToJSVal = unIDBKeyRange
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBKeyRange where
pFromJSVal = IDBKeyRange
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBKeyRange where
toJSVal = return . unIDBKeyRange
{-# INLINE toJSVal #-}
instance FromJSVal IDBKeyRange where
fromJSVal v = fmap IDBKeyRange <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBKeyRange
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBKeyRange where
makeObject = makeObject . unIDBKeyRange
instance IsGObject IDBKeyRange where
typeGType _ = gTypeIDBKeyRange
{-# INLINE typeGType #-}
noIDBKeyRange :: Maybe IDBKeyRange
noIDBKeyRange = Nothing
{-# INLINE noIDBKeyRange #-}
gTypeIDBKeyRange :: JSM GType
gTypeIDBKeyRange = GType . Object <$> jsg "IDBKeyRange"
newtype IDBObjectStore = IDBObjectStore { unIDBObjectStore :: JSVal }
instance PToJSVal IDBObjectStore where
pToJSVal = unIDBObjectStore
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBObjectStore where
pFromJSVal = IDBObjectStore
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBObjectStore where
toJSVal = return . unIDBObjectStore
{-# INLINE toJSVal #-}
instance FromJSVal IDBObjectStore where
fromJSVal v = fmap IDBObjectStore <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBObjectStore
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBObjectStore where
makeObject = makeObject . unIDBObjectStore
instance IsGObject IDBObjectStore where
typeGType _ = gTypeIDBObjectStore
{-# INLINE typeGType #-}
noIDBObjectStore :: Maybe IDBObjectStore
noIDBObjectStore = Nothing
{-# INLINE noIDBObjectStore #-}
gTypeIDBObjectStore :: JSM GType
gTypeIDBObjectStore = GType . Object <$> jsg "IDBObjectStore"
newtype IDBObjectStoreParameters = IDBObjectStoreParameters { unIDBObjectStoreParameters :: JSVal }
instance PToJSVal IDBObjectStoreParameters where
pToJSVal = unIDBObjectStoreParameters
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBObjectStoreParameters where
pFromJSVal = IDBObjectStoreParameters
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBObjectStoreParameters where
toJSVal = return . unIDBObjectStoreParameters
{-# INLINE toJSVal #-}
instance FromJSVal IDBObjectStoreParameters where
fromJSVal v = fmap IDBObjectStoreParameters <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBObjectStoreParameters
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBObjectStoreParameters where
makeObject = makeObject . unIDBObjectStoreParameters
instance IsGObject IDBObjectStoreParameters where
typeGType _ = gTypeIDBObjectStoreParameters
{-# INLINE typeGType #-}
noIDBObjectStoreParameters :: Maybe IDBObjectStoreParameters
noIDBObjectStoreParameters = Nothing
{-# INLINE noIDBObjectStoreParameters #-}
gTypeIDBObjectStoreParameters :: JSM GType
gTypeIDBObjectStoreParameters = GType . Object <$> jsg "IDBObjectStoreParameters"
newtype IDBOpenDBRequest = IDBOpenDBRequest { unIDBOpenDBRequest :: JSVal }
instance PToJSVal IDBOpenDBRequest where
pToJSVal = unIDBOpenDBRequest
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBOpenDBRequest where
pFromJSVal = IDBOpenDBRequest
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBOpenDBRequest where
toJSVal = return . unIDBOpenDBRequest
{-# INLINE toJSVal #-}
instance FromJSVal IDBOpenDBRequest where
fromJSVal v = fmap IDBOpenDBRequest <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBOpenDBRequest
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBOpenDBRequest where
makeObject = makeObject . unIDBOpenDBRequest
instance IsIDBRequest IDBOpenDBRequest
instance IsEventTarget IDBOpenDBRequest
instance IsGObject IDBOpenDBRequest where
typeGType _ = gTypeIDBOpenDBRequest
{-# INLINE typeGType #-}
noIDBOpenDBRequest :: Maybe IDBOpenDBRequest
noIDBOpenDBRequest = Nothing
{-# INLINE noIDBOpenDBRequest #-}
gTypeIDBOpenDBRequest :: JSM GType
gTypeIDBOpenDBRequest = GType . Object <$> jsg "IDBOpenDBRequest"
newtype IDBRequest = IDBRequest { unIDBRequest :: JSVal }
instance PToJSVal IDBRequest where
pToJSVal = unIDBRequest
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBRequest where
pFromJSVal = IDBRequest
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBRequest where
toJSVal = return . unIDBRequest
{-# INLINE toJSVal #-}
instance FromJSVal IDBRequest where
fromJSVal v = fmap IDBRequest <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBRequest
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBRequest where
makeObject = makeObject . unIDBRequest
class (IsEventTarget o, IsGObject o) => IsIDBRequest o
toIDBRequest :: IsIDBRequest o => o -> IDBRequest
toIDBRequest = IDBRequest . coerce
instance IsIDBRequest IDBRequest
instance IsEventTarget IDBRequest
instance IsGObject IDBRequest where
typeGType _ = gTypeIDBRequest
{-# INLINE typeGType #-}
noIDBRequest :: Maybe IDBRequest
noIDBRequest = Nothing
{-# INLINE noIDBRequest #-}
gTypeIDBRequest :: JSM GType
gTypeIDBRequest = GType . Object <$> jsg "IDBRequest"
newtype IDBTransaction = IDBTransaction { unIDBTransaction :: JSVal }
instance PToJSVal IDBTransaction where
pToJSVal = unIDBTransaction
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBTransaction where
pFromJSVal = IDBTransaction
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBTransaction where
toJSVal = return . unIDBTransaction
{-# INLINE toJSVal #-}
instance FromJSVal IDBTransaction where
fromJSVal v = fmap IDBTransaction <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBTransaction
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBTransaction where
makeObject = makeObject . unIDBTransaction
instance IsEventTarget IDBTransaction
instance IsGObject IDBTransaction where
typeGType _ = gTypeIDBTransaction
{-# INLINE typeGType #-}
noIDBTransaction :: Maybe IDBTransaction
noIDBTransaction = Nothing
{-# INLINE noIDBTransaction #-}
gTypeIDBTransaction :: JSM GType
gTypeIDBTransaction = GType . Object <$> jsg "IDBTransaction"
newtype IDBVersionChangeEvent = IDBVersionChangeEvent { unIDBVersionChangeEvent :: JSVal }
instance PToJSVal IDBVersionChangeEvent where
pToJSVal = unIDBVersionChangeEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBVersionChangeEvent where
pFromJSVal = IDBVersionChangeEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBVersionChangeEvent where
toJSVal = return . unIDBVersionChangeEvent
{-# INLINE toJSVal #-}
instance FromJSVal IDBVersionChangeEvent where
fromJSVal v = fmap IDBVersionChangeEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBVersionChangeEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBVersionChangeEvent where
makeObject = makeObject . unIDBVersionChangeEvent
instance IsEvent IDBVersionChangeEvent
instance IsGObject IDBVersionChangeEvent where
typeGType _ = gTypeIDBVersionChangeEvent
{-# INLINE typeGType #-}
noIDBVersionChangeEvent :: Maybe IDBVersionChangeEvent
noIDBVersionChangeEvent = Nothing
{-# INLINE noIDBVersionChangeEvent #-}
gTypeIDBVersionChangeEvent :: JSM GType
gTypeIDBVersionChangeEvent = GType . Object <$> jsg "IDBVersionChangeEvent"
newtype IDBVersionChangeEventInit = IDBVersionChangeEventInit { unIDBVersionChangeEventInit :: JSVal }
instance PToJSVal IDBVersionChangeEventInit where
pToJSVal = unIDBVersionChangeEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal IDBVersionChangeEventInit where
pFromJSVal = IDBVersionChangeEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal IDBVersionChangeEventInit where
toJSVal = return . unIDBVersionChangeEventInit
{-# INLINE toJSVal #-}
instance FromJSVal IDBVersionChangeEventInit where
fromJSVal v = fmap IDBVersionChangeEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IDBVersionChangeEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IDBVersionChangeEventInit where
makeObject = makeObject . unIDBVersionChangeEventInit
instance IsEventInit IDBVersionChangeEventInit
instance IsGObject IDBVersionChangeEventInit where
typeGType _ = gTypeIDBVersionChangeEventInit
{-# INLINE typeGType #-}
noIDBVersionChangeEventInit :: Maybe IDBVersionChangeEventInit
noIDBVersionChangeEventInit = Nothing
{-# INLINE noIDBVersionChangeEventInit #-}
gTypeIDBVersionChangeEventInit :: JSM GType
gTypeIDBVersionChangeEventInit = GType . Object <$> jsg "IDBVersionChangeEventInit"
newtype ImageData = ImageData { unImageData :: JSVal }
instance PToJSVal ImageData where
pToJSVal = unImageData
{-# INLINE pToJSVal #-}
instance PFromJSVal ImageData where
pFromJSVal = ImageData
{-# INLINE pFromJSVal #-}
instance ToJSVal ImageData where
toJSVal = return . unImageData
{-# INLINE toJSVal #-}
instance FromJSVal ImageData where
fromJSVal v = fmap ImageData <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ImageData
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ImageData where
makeObject = makeObject . unImageData
instance IsGObject ImageData where
typeGType _ = gTypeImageData
{-# INLINE typeGType #-}
noImageData :: Maybe ImageData
noImageData = Nothing
{-# INLINE noImageData #-}
gTypeImageData :: JSM GType
gTypeImageData = GType . Object <$> jsg "ImageData"
newtype InputEvent = InputEvent { unInputEvent :: JSVal }
instance PToJSVal InputEvent where
pToJSVal = unInputEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal InputEvent where
pFromJSVal = InputEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal InputEvent where
toJSVal = return . unInputEvent
{-# INLINE toJSVal #-}
instance FromJSVal InputEvent where
fromJSVal v = fmap InputEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . InputEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject InputEvent where
makeObject = makeObject . unInputEvent
instance IsUIEvent InputEvent
instance IsEvent InputEvent
instance IsGObject InputEvent where
typeGType _ = gTypeInputEvent
{-# INLINE typeGType #-}
noInputEvent :: Maybe InputEvent
noInputEvent = Nothing
{-# INLINE noInputEvent #-}
gTypeInputEvent :: JSM GType
gTypeInputEvent = GType . Object <$> jsg "InputEvent"
newtype InputEventInit = InputEventInit { unInputEventInit :: JSVal }
instance PToJSVal InputEventInit where
pToJSVal = unInputEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal InputEventInit where
pFromJSVal = InputEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal InputEventInit where
toJSVal = return . unInputEventInit
{-# INLINE toJSVal #-}
instance FromJSVal InputEventInit where
fromJSVal v = fmap InputEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . InputEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject InputEventInit where
makeObject = makeObject . unInputEventInit
instance IsUIEventInit InputEventInit
instance IsEventInit InputEventInit
instance IsGObject InputEventInit where
typeGType _ = gTypeInputEventInit
{-# INLINE typeGType #-}
noInputEventInit :: Maybe InputEventInit
noInputEventInit = Nothing
{-# INLINE noInputEventInit #-}
gTypeInputEventInit :: JSM GType
gTypeInputEventInit = GType . Object <$> jsg "InputEventInit"
newtype InspectorFrontendHost = InspectorFrontendHost { unInspectorFrontendHost :: JSVal }
instance PToJSVal InspectorFrontendHost where
pToJSVal = unInspectorFrontendHost
{-# INLINE pToJSVal #-}
instance PFromJSVal InspectorFrontendHost where
pFromJSVal = InspectorFrontendHost
{-# INLINE pFromJSVal #-}
instance ToJSVal InspectorFrontendHost where
toJSVal = return . unInspectorFrontendHost
{-# INLINE toJSVal #-}
instance FromJSVal InspectorFrontendHost where
fromJSVal v = fmap InspectorFrontendHost <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . InspectorFrontendHost
{-# INLINE fromJSValUnchecked #-}
instance MakeObject InspectorFrontendHost where
makeObject = makeObject . unInspectorFrontendHost
instance IsGObject InspectorFrontendHost where
typeGType _ = gTypeInspectorFrontendHost
{-# INLINE typeGType #-}
noInspectorFrontendHost :: Maybe InspectorFrontendHost
noInspectorFrontendHost = Nothing
{-# INLINE noInspectorFrontendHost #-}
gTypeInspectorFrontendHost :: JSM GType
gTypeInspectorFrontendHost = GType . Object <$> jsg "InspectorFrontendHost"
newtype IntersectionObserver = IntersectionObserver { unIntersectionObserver :: JSVal }
instance PToJSVal IntersectionObserver where
pToJSVal = unIntersectionObserver
{-# INLINE pToJSVal #-}
instance PFromJSVal IntersectionObserver where
pFromJSVal = IntersectionObserver
{-# INLINE pFromJSVal #-}
instance ToJSVal IntersectionObserver where
toJSVal = return . unIntersectionObserver
{-# INLINE toJSVal #-}
instance FromJSVal IntersectionObserver where
fromJSVal v = fmap IntersectionObserver <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IntersectionObserver
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IntersectionObserver where
makeObject = makeObject . unIntersectionObserver
instance IsGObject IntersectionObserver where
typeGType _ = gTypeIntersectionObserver
{-# INLINE typeGType #-}
noIntersectionObserver :: Maybe IntersectionObserver
noIntersectionObserver = Nothing
{-# INLINE noIntersectionObserver #-}
gTypeIntersectionObserver :: JSM GType
gTypeIntersectionObserver = GType . Object <$> jsg "IntersectionObserver"
newtype IntersectionObserverEntry = IntersectionObserverEntry { unIntersectionObserverEntry :: JSVal }
instance PToJSVal IntersectionObserverEntry where
pToJSVal = unIntersectionObserverEntry
{-# INLINE pToJSVal #-}
instance PFromJSVal IntersectionObserverEntry where
pFromJSVal = IntersectionObserverEntry
{-# INLINE pFromJSVal #-}
instance ToJSVal IntersectionObserverEntry where
toJSVal = return . unIntersectionObserverEntry
{-# INLINE toJSVal #-}
instance FromJSVal IntersectionObserverEntry where
fromJSVal v = fmap IntersectionObserverEntry <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IntersectionObserverEntry
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IntersectionObserverEntry where
makeObject = makeObject . unIntersectionObserverEntry
instance IsGObject IntersectionObserverEntry where
typeGType _ = gTypeIntersectionObserverEntry
{-# INLINE typeGType #-}
noIntersectionObserverEntry :: Maybe IntersectionObserverEntry
noIntersectionObserverEntry = Nothing
{-# INLINE noIntersectionObserverEntry #-}
gTypeIntersectionObserverEntry :: JSM GType
gTypeIntersectionObserverEntry = GType . Object <$> jsg "IntersectionObserverEntry"
newtype IntersectionObserverEntryInit = IntersectionObserverEntryInit { unIntersectionObserverEntryInit :: JSVal }
instance PToJSVal IntersectionObserverEntryInit where
pToJSVal = unIntersectionObserverEntryInit
{-# INLINE pToJSVal #-}
instance PFromJSVal IntersectionObserverEntryInit where
pFromJSVal = IntersectionObserverEntryInit
{-# INLINE pFromJSVal #-}
instance ToJSVal IntersectionObserverEntryInit where
toJSVal = return . unIntersectionObserverEntryInit
{-# INLINE toJSVal #-}
instance FromJSVal IntersectionObserverEntryInit where
fromJSVal v = fmap IntersectionObserverEntryInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IntersectionObserverEntryInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IntersectionObserverEntryInit where
makeObject = makeObject . unIntersectionObserverEntryInit
instance IsGObject IntersectionObserverEntryInit where
typeGType _ = gTypeIntersectionObserverEntryInit
{-# INLINE typeGType #-}
noIntersectionObserverEntryInit :: Maybe IntersectionObserverEntryInit
noIntersectionObserverEntryInit = Nothing
{-# INLINE noIntersectionObserverEntryInit #-}
gTypeIntersectionObserverEntryInit :: JSM GType
gTypeIntersectionObserverEntryInit = GType . Object <$> jsg "IntersectionObserverEntryInit"
newtype IntersectionObserverInit = IntersectionObserverInit { unIntersectionObserverInit :: JSVal }
instance PToJSVal IntersectionObserverInit where
pToJSVal = unIntersectionObserverInit
{-# INLINE pToJSVal #-}
instance PFromJSVal IntersectionObserverInit where
pFromJSVal = IntersectionObserverInit
{-# INLINE pFromJSVal #-}
instance ToJSVal IntersectionObserverInit where
toJSVal = return . unIntersectionObserverInit
{-# INLINE toJSVal #-}
instance FromJSVal IntersectionObserverInit where
fromJSVal v = fmap IntersectionObserverInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . IntersectionObserverInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject IntersectionObserverInit where
makeObject = makeObject . unIntersectionObserverInit
instance IsGObject IntersectionObserverInit where
typeGType _ = gTypeIntersectionObserverInit
{-# INLINE typeGType #-}
noIntersectionObserverInit :: Maybe IntersectionObserverInit
noIntersectionObserverInit = Nothing
{-# INLINE noIntersectionObserverInit #-}
gTypeIntersectionObserverInit :: JSM GType
gTypeIntersectionObserverInit = GType . Object <$> jsg "IntersectionObserverInit"
newtype JsonWebKey = JsonWebKey { unJsonWebKey :: JSVal }
instance PToJSVal JsonWebKey where
pToJSVal = unJsonWebKey
{-# INLINE pToJSVal #-}
instance PFromJSVal JsonWebKey where
pFromJSVal = JsonWebKey
{-# INLINE pFromJSVal #-}
instance ToJSVal JsonWebKey where
toJSVal = return . unJsonWebKey
{-# INLINE toJSVal #-}
instance FromJSVal JsonWebKey where
fromJSVal v = fmap JsonWebKey <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . JsonWebKey
{-# INLINE fromJSValUnchecked #-}
instance MakeObject JsonWebKey where
makeObject = makeObject . unJsonWebKey
instance IsGObject JsonWebKey where
typeGType _ = gTypeJsonWebKey
{-# INLINE typeGType #-}
noJsonWebKey :: Maybe JsonWebKey
noJsonWebKey = Nothing
{-# INLINE noJsonWebKey #-}
gTypeJsonWebKey :: JSM GType
gTypeJsonWebKey = GType . Object <$> jsg "JsonWebKey"
newtype KeyboardEvent = KeyboardEvent { unKeyboardEvent :: JSVal }
instance PToJSVal KeyboardEvent where
pToJSVal = unKeyboardEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal KeyboardEvent where
pFromJSVal = KeyboardEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal KeyboardEvent where
toJSVal = return . unKeyboardEvent
{-# INLINE toJSVal #-}
instance FromJSVal KeyboardEvent where
fromJSVal v = fmap KeyboardEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . KeyboardEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject KeyboardEvent where
makeObject = makeObject . unKeyboardEvent
instance IsUIEvent KeyboardEvent
instance IsEvent KeyboardEvent
instance IsGObject KeyboardEvent where
typeGType _ = gTypeKeyboardEvent
{-# INLINE typeGType #-}
noKeyboardEvent :: Maybe KeyboardEvent
noKeyboardEvent = Nothing
{-# INLINE noKeyboardEvent #-}
gTypeKeyboardEvent :: JSM GType
gTypeKeyboardEvent = GType . Object <$> jsg "KeyboardEvent"
newtype KeyboardEventInit = KeyboardEventInit { unKeyboardEventInit :: JSVal }
instance PToJSVal KeyboardEventInit where
pToJSVal = unKeyboardEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal KeyboardEventInit where
pFromJSVal = KeyboardEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal KeyboardEventInit where
toJSVal = return . unKeyboardEventInit
{-# INLINE toJSVal #-}
instance FromJSVal KeyboardEventInit where
fromJSVal v = fmap KeyboardEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . KeyboardEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject KeyboardEventInit where
makeObject = makeObject . unKeyboardEventInit
instance IsEventModifierInit KeyboardEventInit
instance IsUIEventInit KeyboardEventInit
instance IsEventInit KeyboardEventInit
instance IsGObject KeyboardEventInit where
typeGType _ = gTypeKeyboardEventInit
{-# INLINE typeGType #-}
noKeyboardEventInit :: Maybe KeyboardEventInit
noKeyboardEventInit = Nothing
{-# INLINE noKeyboardEventInit #-}
gTypeKeyboardEventInit :: JSM GType
gTypeKeyboardEventInit = GType . Object <$> jsg "KeyboardEventInit"
newtype KeyframeEffect = KeyframeEffect { unKeyframeEffect :: JSVal }
instance PToJSVal KeyframeEffect where
pToJSVal = unKeyframeEffect
{-# INLINE pToJSVal #-}
instance PFromJSVal KeyframeEffect where
pFromJSVal = KeyframeEffect
{-# INLINE pFromJSVal #-}
instance ToJSVal KeyframeEffect where
toJSVal = return . unKeyframeEffect
{-# INLINE toJSVal #-}
instance FromJSVal KeyframeEffect where
fromJSVal v = fmap KeyframeEffect <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . KeyframeEffect
{-# INLINE fromJSValUnchecked #-}
instance MakeObject KeyframeEffect where
makeObject = makeObject . unKeyframeEffect
instance IsAnimationEffect KeyframeEffect
instance IsGObject KeyframeEffect where
typeGType _ = gTypeKeyframeEffect
{-# INLINE typeGType #-}
noKeyframeEffect :: Maybe KeyframeEffect
noKeyframeEffect = Nothing
{-# INLINE noKeyframeEffect #-}
gTypeKeyframeEffect :: JSM GType
gTypeKeyframeEffect = GType . Object <$> jsg "KeyframeEffect"
newtype Location = Location { unLocation :: JSVal }
instance PToJSVal Location where
pToJSVal = unLocation
{-# INLINE pToJSVal #-}
instance PFromJSVal Location where
pFromJSVal = Location
{-# INLINE pFromJSVal #-}
instance ToJSVal Location where
toJSVal = return . unLocation
{-# INLINE toJSVal #-}
instance FromJSVal Location where
fromJSVal v = fmap Location <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Location
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Location where
makeObject = makeObject . unLocation
instance IsGObject Location where
typeGType _ = gTypeLocation
{-# INLINE typeGType #-}
noLocation :: Maybe Location
noLocation = Nothing
{-# INLINE noLocation #-}
gTypeLocation :: JSM GType
gTypeLocation = GType . Object <$> jsg "Location"
newtype LongRange = LongRange { unLongRange :: JSVal }
instance PToJSVal LongRange where
pToJSVal = unLongRange
{-# INLINE pToJSVal #-}
instance PFromJSVal LongRange where
pFromJSVal = LongRange
{-# INLINE pFromJSVal #-}
instance ToJSVal LongRange where
toJSVal = return . unLongRange
{-# INLINE toJSVal #-}
instance FromJSVal LongRange where
fromJSVal v = fmap LongRange <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . LongRange
{-# INLINE fromJSValUnchecked #-}
instance MakeObject LongRange where
makeObject = makeObject . unLongRange
class (IsGObject o) => IsLongRange o
toLongRange :: IsLongRange o => o -> LongRange
toLongRange = LongRange . coerce
instance IsLongRange LongRange
instance IsGObject LongRange where
typeGType _ = gTypeLongRange
{-# INLINE typeGType #-}
noLongRange :: Maybe LongRange
noLongRange = Nothing
{-# INLINE noLongRange #-}
gTypeLongRange :: JSM GType
gTypeLongRange = GType . Object <$> jsg "LongRange"
newtype MediaController = MediaController { unMediaController :: JSVal }
instance PToJSVal MediaController where
pToJSVal = unMediaController
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaController where
pFromJSVal = MediaController
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaController where
toJSVal = return . unMediaController
{-# INLINE toJSVal #-}
instance FromJSVal MediaController where
fromJSVal v = fmap MediaController <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaController
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaController where
makeObject = makeObject . unMediaController
instance IsEventTarget MediaController
instance IsGObject MediaController where
typeGType _ = gTypeMediaController
{-# INLINE typeGType #-}
noMediaController :: Maybe MediaController
noMediaController = Nothing
{-# INLINE noMediaController #-}
gTypeMediaController :: JSM GType
gTypeMediaController = GType . Object <$> jsg "MediaController"
newtype MediaControlsHost = MediaControlsHost { unMediaControlsHost :: JSVal }
instance PToJSVal MediaControlsHost where
pToJSVal = unMediaControlsHost
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaControlsHost where
pFromJSVal = MediaControlsHost
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaControlsHost where
toJSVal = return . unMediaControlsHost
{-# INLINE toJSVal #-}
instance FromJSVal MediaControlsHost where
fromJSVal v = fmap MediaControlsHost <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaControlsHost
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaControlsHost where
makeObject = makeObject . unMediaControlsHost
instance IsGObject MediaControlsHost where
typeGType _ = gTypeMediaControlsHost
{-# INLINE typeGType #-}
noMediaControlsHost :: Maybe MediaControlsHost
noMediaControlsHost = Nothing
{-# INLINE noMediaControlsHost #-}
gTypeMediaControlsHost :: JSM GType
gTypeMediaControlsHost = GType . Object <$> jsg "MediaControlsHost"
newtype MediaDeviceInfo = MediaDeviceInfo { unMediaDeviceInfo :: JSVal }
instance PToJSVal MediaDeviceInfo where
pToJSVal = unMediaDeviceInfo
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaDeviceInfo where
pFromJSVal = MediaDeviceInfo
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaDeviceInfo where
toJSVal = return . unMediaDeviceInfo
{-# INLINE toJSVal #-}
instance FromJSVal MediaDeviceInfo where
fromJSVal v = fmap MediaDeviceInfo <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaDeviceInfo
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaDeviceInfo where
makeObject = makeObject . unMediaDeviceInfo
instance IsGObject MediaDeviceInfo where
typeGType _ = gTypeMediaDeviceInfo
{-# INLINE typeGType #-}
noMediaDeviceInfo :: Maybe MediaDeviceInfo
noMediaDeviceInfo = Nothing
{-# INLINE noMediaDeviceInfo #-}
gTypeMediaDeviceInfo :: JSM GType
gTypeMediaDeviceInfo = GType . Object <$> jsg "MediaDeviceInfo"
newtype MediaDevices = MediaDevices { unMediaDevices :: JSVal }
instance PToJSVal MediaDevices where
pToJSVal = unMediaDevices
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaDevices where
pFromJSVal = MediaDevices
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaDevices where
toJSVal = return . unMediaDevices
{-# INLINE toJSVal #-}
instance FromJSVal MediaDevices where
fromJSVal v = fmap MediaDevices <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaDevices
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaDevices where
makeObject = makeObject . unMediaDevices
instance IsGObject MediaDevices where
typeGType _ = gTypeMediaDevices
{-# INLINE typeGType #-}
noMediaDevices :: Maybe MediaDevices
noMediaDevices = Nothing
{-# INLINE noMediaDevices #-}
gTypeMediaDevices :: JSM GType
gTypeMediaDevices = GType . Object <$> jsg "MediaDevices"
newtype MediaElementAudioSourceNode = MediaElementAudioSourceNode { unMediaElementAudioSourceNode :: JSVal }
instance PToJSVal MediaElementAudioSourceNode where
pToJSVal = unMediaElementAudioSourceNode
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaElementAudioSourceNode where
pFromJSVal = MediaElementAudioSourceNode
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaElementAudioSourceNode where
toJSVal = return . unMediaElementAudioSourceNode
{-# INLINE toJSVal #-}
instance FromJSVal MediaElementAudioSourceNode where
fromJSVal v = fmap MediaElementAudioSourceNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaElementAudioSourceNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaElementAudioSourceNode where
makeObject = makeObject . unMediaElementAudioSourceNode
instance IsAudioNode MediaElementAudioSourceNode
instance IsEventTarget MediaElementAudioSourceNode
instance IsGObject MediaElementAudioSourceNode where
typeGType _ = gTypeMediaElementAudioSourceNode
{-# INLINE typeGType #-}
noMediaElementAudioSourceNode :: Maybe MediaElementAudioSourceNode
noMediaElementAudioSourceNode = Nothing
{-# INLINE noMediaElementAudioSourceNode #-}
gTypeMediaElementAudioSourceNode :: JSM GType
gTypeMediaElementAudioSourceNode = GType . Object <$> jsg "MediaElementAudioSourceNode"
newtype MediaEncryptedEvent = MediaEncryptedEvent { unMediaEncryptedEvent :: JSVal }
instance PToJSVal MediaEncryptedEvent where
pToJSVal = unMediaEncryptedEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaEncryptedEvent where
pFromJSVal = MediaEncryptedEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaEncryptedEvent where
toJSVal = return . unMediaEncryptedEvent
{-# INLINE toJSVal #-}
instance FromJSVal MediaEncryptedEvent where
fromJSVal v = fmap MediaEncryptedEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaEncryptedEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaEncryptedEvent where
makeObject = makeObject . unMediaEncryptedEvent
instance IsEvent MediaEncryptedEvent
instance IsGObject MediaEncryptedEvent where
typeGType _ = gTypeMediaEncryptedEvent
{-# INLINE typeGType #-}
noMediaEncryptedEvent :: Maybe MediaEncryptedEvent
noMediaEncryptedEvent = Nothing
{-# INLINE noMediaEncryptedEvent #-}
gTypeMediaEncryptedEvent :: JSM GType
gTypeMediaEncryptedEvent = GType . Object <$> jsg "MediaEncryptedEvent"
newtype MediaEncryptedEventInit = MediaEncryptedEventInit { unMediaEncryptedEventInit :: JSVal }
instance PToJSVal MediaEncryptedEventInit where
pToJSVal = unMediaEncryptedEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaEncryptedEventInit where
pFromJSVal = MediaEncryptedEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaEncryptedEventInit where
toJSVal = return . unMediaEncryptedEventInit
{-# INLINE toJSVal #-}
instance FromJSVal MediaEncryptedEventInit where
fromJSVal v = fmap MediaEncryptedEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaEncryptedEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaEncryptedEventInit where
makeObject = makeObject . unMediaEncryptedEventInit
instance IsEventInit MediaEncryptedEventInit
instance IsGObject MediaEncryptedEventInit where
typeGType _ = gTypeMediaEncryptedEventInit
{-# INLINE typeGType #-}
noMediaEncryptedEventInit :: Maybe MediaEncryptedEventInit
noMediaEncryptedEventInit = Nothing
{-# INLINE noMediaEncryptedEventInit #-}
gTypeMediaEncryptedEventInit :: JSM GType
gTypeMediaEncryptedEventInit = GType . Object <$> jsg "MediaEncryptedEventInit"
newtype MediaError = MediaError { unMediaError :: JSVal }
instance PToJSVal MediaError where
pToJSVal = unMediaError
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaError where
pFromJSVal = MediaError
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaError where
toJSVal = return . unMediaError
{-# INLINE toJSVal #-}
instance FromJSVal MediaError where
fromJSVal v = fmap MediaError <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaError
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaError where
makeObject = makeObject . unMediaError
instance IsGObject MediaError where
typeGType _ = gTypeMediaError
{-# INLINE typeGType #-}
noMediaError :: Maybe MediaError
noMediaError = Nothing
{-# INLINE noMediaError #-}
gTypeMediaError :: JSM GType
gTypeMediaError = GType . Object <$> jsg "MediaError"
newtype MediaKeyMessageEvent = MediaKeyMessageEvent { unMediaKeyMessageEvent :: JSVal }
instance PToJSVal MediaKeyMessageEvent where
pToJSVal = unMediaKeyMessageEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaKeyMessageEvent where
pFromJSVal = MediaKeyMessageEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaKeyMessageEvent where
toJSVal = return . unMediaKeyMessageEvent
{-# INLINE toJSVal #-}
instance FromJSVal MediaKeyMessageEvent where
fromJSVal v = fmap MediaKeyMessageEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaKeyMessageEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaKeyMessageEvent where
makeObject = makeObject . unMediaKeyMessageEvent
instance IsEvent MediaKeyMessageEvent
instance IsGObject MediaKeyMessageEvent where
typeGType _ = gTypeMediaKeyMessageEvent
{-# INLINE typeGType #-}
noMediaKeyMessageEvent :: Maybe MediaKeyMessageEvent
noMediaKeyMessageEvent = Nothing
{-# INLINE noMediaKeyMessageEvent #-}
gTypeMediaKeyMessageEvent :: JSM GType
gTypeMediaKeyMessageEvent = GType . Object <$> jsg "WebKitMediaKeyMessageEvent"
newtype MediaKeyMessageEventInit = MediaKeyMessageEventInit { unMediaKeyMessageEventInit :: JSVal }
instance PToJSVal MediaKeyMessageEventInit where
pToJSVal = unMediaKeyMessageEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaKeyMessageEventInit where
pFromJSVal = MediaKeyMessageEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaKeyMessageEventInit where
toJSVal = return . unMediaKeyMessageEventInit
{-# INLINE toJSVal #-}
instance FromJSVal MediaKeyMessageEventInit where
fromJSVal v = fmap MediaKeyMessageEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaKeyMessageEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaKeyMessageEventInit where
makeObject = makeObject . unMediaKeyMessageEventInit
instance IsEventInit MediaKeyMessageEventInit
instance IsGObject MediaKeyMessageEventInit where
typeGType _ = gTypeMediaKeyMessageEventInit
{-# INLINE typeGType #-}
noMediaKeyMessageEventInit :: Maybe MediaKeyMessageEventInit
noMediaKeyMessageEventInit = Nothing
{-# INLINE noMediaKeyMessageEventInit #-}
gTypeMediaKeyMessageEventInit :: JSM GType
gTypeMediaKeyMessageEventInit = GType . Object <$> jsg "MediaKeyMessageEventInit"
newtype MediaKeySession = MediaKeySession { unMediaKeySession :: JSVal }
instance PToJSVal MediaKeySession where
pToJSVal = unMediaKeySession
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaKeySession where
pFromJSVal = MediaKeySession
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaKeySession where
toJSVal = return . unMediaKeySession
{-# INLINE toJSVal #-}
instance FromJSVal MediaKeySession where
fromJSVal v = fmap MediaKeySession <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaKeySession
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaKeySession where
makeObject = makeObject . unMediaKeySession
instance IsEventTarget MediaKeySession
instance IsGObject MediaKeySession where
typeGType _ = gTypeMediaKeySession
{-# INLINE typeGType #-}
noMediaKeySession :: Maybe MediaKeySession
noMediaKeySession = Nothing
{-# INLINE noMediaKeySession #-}
gTypeMediaKeySession :: JSM GType
gTypeMediaKeySession = GType . Object <$> jsg "WebKitMediaKeySession"
newtype MediaKeyStatusMap = MediaKeyStatusMap { unMediaKeyStatusMap :: JSVal }
instance PToJSVal MediaKeyStatusMap where
pToJSVal = unMediaKeyStatusMap
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaKeyStatusMap where
pFromJSVal = MediaKeyStatusMap
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaKeyStatusMap where
toJSVal = return . unMediaKeyStatusMap
{-# INLINE toJSVal #-}
instance FromJSVal MediaKeyStatusMap where
fromJSVal v = fmap MediaKeyStatusMap <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaKeyStatusMap
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaKeyStatusMap where
makeObject = makeObject . unMediaKeyStatusMap
instance IsGObject MediaKeyStatusMap where
typeGType _ = gTypeMediaKeyStatusMap
{-# INLINE typeGType #-}
noMediaKeyStatusMap :: Maybe MediaKeyStatusMap
noMediaKeyStatusMap = Nothing
{-# INLINE noMediaKeyStatusMap #-}
gTypeMediaKeyStatusMap :: JSM GType
gTypeMediaKeyStatusMap = GType . Object <$> jsg "MediaKeyStatusMap"
newtype MediaKeySystemAccess = MediaKeySystemAccess { unMediaKeySystemAccess :: JSVal }
instance PToJSVal MediaKeySystemAccess where
pToJSVal = unMediaKeySystemAccess
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaKeySystemAccess where
pFromJSVal = MediaKeySystemAccess
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaKeySystemAccess where
toJSVal = return . unMediaKeySystemAccess
{-# INLINE toJSVal #-}
instance FromJSVal MediaKeySystemAccess where
fromJSVal v = fmap MediaKeySystemAccess <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaKeySystemAccess
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaKeySystemAccess where
makeObject = makeObject . unMediaKeySystemAccess
instance IsGObject MediaKeySystemAccess where
typeGType _ = gTypeMediaKeySystemAccess
{-# INLINE typeGType #-}
noMediaKeySystemAccess :: Maybe MediaKeySystemAccess
noMediaKeySystemAccess = Nothing
{-# INLINE noMediaKeySystemAccess #-}
gTypeMediaKeySystemAccess :: JSM GType
gTypeMediaKeySystemAccess = GType . Object <$> jsg "MediaKeySystemAccess"
newtype MediaKeySystemConfiguration = MediaKeySystemConfiguration { unMediaKeySystemConfiguration :: JSVal }
instance PToJSVal MediaKeySystemConfiguration where
pToJSVal = unMediaKeySystemConfiguration
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaKeySystemConfiguration where
pFromJSVal = MediaKeySystemConfiguration
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaKeySystemConfiguration where
toJSVal = return . unMediaKeySystemConfiguration
{-# INLINE toJSVal #-}
instance FromJSVal MediaKeySystemConfiguration where
fromJSVal v = fmap MediaKeySystemConfiguration <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaKeySystemConfiguration
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaKeySystemConfiguration where
makeObject = makeObject . unMediaKeySystemConfiguration
instance IsGObject MediaKeySystemConfiguration where
typeGType _ = gTypeMediaKeySystemConfiguration
{-# INLINE typeGType #-}
noMediaKeySystemConfiguration :: Maybe MediaKeySystemConfiguration
noMediaKeySystemConfiguration = Nothing
{-# INLINE noMediaKeySystemConfiguration #-}
gTypeMediaKeySystemConfiguration :: JSM GType
gTypeMediaKeySystemConfiguration = GType . Object <$> jsg "MediaKeySystemConfiguration"
newtype MediaKeySystemMediaCapability = MediaKeySystemMediaCapability { unMediaKeySystemMediaCapability :: JSVal }
instance PToJSVal MediaKeySystemMediaCapability where
pToJSVal = unMediaKeySystemMediaCapability
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaKeySystemMediaCapability where
pFromJSVal = MediaKeySystemMediaCapability
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaKeySystemMediaCapability where
toJSVal = return . unMediaKeySystemMediaCapability
{-# INLINE toJSVal #-}
instance FromJSVal MediaKeySystemMediaCapability where
fromJSVal v = fmap MediaKeySystemMediaCapability <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaKeySystemMediaCapability
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaKeySystemMediaCapability where
makeObject = makeObject . unMediaKeySystemMediaCapability
instance IsGObject MediaKeySystemMediaCapability where
typeGType _ = gTypeMediaKeySystemMediaCapability
{-# INLINE typeGType #-}
noMediaKeySystemMediaCapability :: Maybe MediaKeySystemMediaCapability
noMediaKeySystemMediaCapability = Nothing
{-# INLINE noMediaKeySystemMediaCapability #-}
gTypeMediaKeySystemMediaCapability :: JSM GType
gTypeMediaKeySystemMediaCapability = GType . Object <$> jsg "MediaKeySystemMediaCapability"
newtype MediaKeys = MediaKeys { unMediaKeys :: JSVal }
instance PToJSVal MediaKeys where
pToJSVal = unMediaKeys
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaKeys where
pFromJSVal = MediaKeys
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaKeys where
toJSVal = return . unMediaKeys
{-# INLINE toJSVal #-}
instance FromJSVal MediaKeys where
fromJSVal v = fmap MediaKeys <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaKeys
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaKeys where
makeObject = makeObject . unMediaKeys
instance IsGObject MediaKeys where
typeGType _ = gTypeMediaKeys
{-# INLINE typeGType #-}
noMediaKeys :: Maybe MediaKeys
noMediaKeys = Nothing
{-# INLINE noMediaKeys #-}
gTypeMediaKeys :: JSM GType
gTypeMediaKeys = GType . Object <$> jsg "WebKitMediaKeys"
newtype MediaList = MediaList { unMediaList :: JSVal }
instance PToJSVal MediaList where
pToJSVal = unMediaList
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaList where
pFromJSVal = MediaList
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaList where
toJSVal = return . unMediaList
{-# INLINE toJSVal #-}
instance FromJSVal MediaList where
fromJSVal v = fmap MediaList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaList where
makeObject = makeObject . unMediaList
instance IsGObject MediaList where
typeGType _ = gTypeMediaList
{-# INLINE typeGType #-}
noMediaList :: Maybe MediaList
noMediaList = Nothing
{-# INLINE noMediaList #-}
gTypeMediaList :: JSM GType
gTypeMediaList = GType . Object <$> jsg "MediaList"
newtype MediaMetadata = MediaMetadata { unMediaMetadata :: JSVal }
instance PToJSVal MediaMetadata where
pToJSVal = unMediaMetadata
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaMetadata where
pFromJSVal = MediaMetadata
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaMetadata where
toJSVal = return . unMediaMetadata
{-# INLINE toJSVal #-}
instance FromJSVal MediaMetadata where
fromJSVal v = fmap MediaMetadata <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaMetadata
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaMetadata where
makeObject = makeObject . unMediaMetadata
instance IsGObject MediaMetadata where
typeGType _ = gTypeMediaMetadata
{-# INLINE typeGType #-}
noMediaMetadata :: Maybe MediaMetadata
noMediaMetadata = Nothing
{-# INLINE noMediaMetadata #-}
gTypeMediaMetadata :: JSM GType
gTypeMediaMetadata = GType . Object <$> jsg "MediaMetadata"
newtype MediaQueryList = MediaQueryList { unMediaQueryList :: JSVal }
instance PToJSVal MediaQueryList where
pToJSVal = unMediaQueryList
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaQueryList where
pFromJSVal = MediaQueryList
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaQueryList where
toJSVal = return . unMediaQueryList
{-# INLINE toJSVal #-}
instance FromJSVal MediaQueryList where
fromJSVal v = fmap MediaQueryList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaQueryList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaQueryList where
makeObject = makeObject . unMediaQueryList
instance IsGObject MediaQueryList where
typeGType _ = gTypeMediaQueryList
{-# INLINE typeGType #-}
noMediaQueryList :: Maybe MediaQueryList
noMediaQueryList = Nothing
{-# INLINE noMediaQueryList #-}
gTypeMediaQueryList :: JSM GType
gTypeMediaQueryList = GType . Object <$> jsg "MediaQueryList"
newtype MediaRemoteControls = MediaRemoteControls { unMediaRemoteControls :: JSVal }
instance PToJSVal MediaRemoteControls where
pToJSVal = unMediaRemoteControls
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaRemoteControls where
pFromJSVal = MediaRemoteControls
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaRemoteControls where
toJSVal = return . unMediaRemoteControls
{-# INLINE toJSVal #-}
instance FromJSVal MediaRemoteControls where
fromJSVal v = fmap MediaRemoteControls <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaRemoteControls
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaRemoteControls where
makeObject = makeObject . unMediaRemoteControls
instance IsEventTarget MediaRemoteControls
instance IsGObject MediaRemoteControls where
typeGType _ = gTypeMediaRemoteControls
{-# INLINE typeGType #-}
noMediaRemoteControls :: Maybe MediaRemoteControls
noMediaRemoteControls = Nothing
{-# INLINE noMediaRemoteControls #-}
gTypeMediaRemoteControls :: JSM GType
gTypeMediaRemoteControls = GType . Object <$> jsg "MediaRemoteControls"
newtype MediaSession = MediaSession { unMediaSession :: JSVal }
instance PToJSVal MediaSession where
pToJSVal = unMediaSession
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaSession where
pFromJSVal = MediaSession
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaSession where
toJSVal = return . unMediaSession
{-# INLINE toJSVal #-}
instance FromJSVal MediaSession where
fromJSVal v = fmap MediaSession <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaSession
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaSession where
makeObject = makeObject . unMediaSession
instance IsGObject MediaSession where
typeGType _ = gTypeMediaSession
{-# INLINE typeGType #-}
noMediaSession :: Maybe MediaSession
noMediaSession = Nothing
{-# INLINE noMediaSession #-}
gTypeMediaSession :: JSM GType
gTypeMediaSession = GType . Object <$> jsg "MediaSession"
newtype MediaSource = MediaSource { unMediaSource :: JSVal }
instance PToJSVal MediaSource where
pToJSVal = unMediaSource
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaSource where
pFromJSVal = MediaSource
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaSource where
toJSVal = return . unMediaSource
{-# INLINE toJSVal #-}
instance FromJSVal MediaSource where
fromJSVal v = fmap MediaSource <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaSource
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaSource where
makeObject = makeObject . unMediaSource
instance IsEventTarget MediaSource
instance IsGObject MediaSource where
typeGType _ = gTypeMediaSource
{-# INLINE typeGType #-}
noMediaSource :: Maybe MediaSource
noMediaSource = Nothing
{-# INLINE noMediaSource #-}
gTypeMediaSource :: JSM GType
gTypeMediaSource = GType . Object <$> jsg "MediaSource"
newtype MediaStream = MediaStream { unMediaStream :: JSVal }
instance PToJSVal MediaStream where
pToJSVal = unMediaStream
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaStream where
pFromJSVal = MediaStream
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaStream where
toJSVal = return . unMediaStream
{-# INLINE toJSVal #-}
instance FromJSVal MediaStream where
fromJSVal v = fmap MediaStream <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaStream
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaStream where
makeObject = makeObject . unMediaStream
instance IsEventTarget MediaStream
instance IsGObject MediaStream where
typeGType _ = gTypeMediaStream
{-# INLINE typeGType #-}
noMediaStream :: Maybe MediaStream
noMediaStream = Nothing
{-# INLINE noMediaStream #-}
gTypeMediaStream :: JSM GType
gTypeMediaStream = GType . Object <$> jsg "webkitMediaStream"
newtype MediaStreamAudioDestinationNode = MediaStreamAudioDestinationNode { unMediaStreamAudioDestinationNode :: JSVal }
instance PToJSVal MediaStreamAudioDestinationNode where
pToJSVal = unMediaStreamAudioDestinationNode
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaStreamAudioDestinationNode where
pFromJSVal = MediaStreamAudioDestinationNode
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaStreamAudioDestinationNode where
toJSVal = return . unMediaStreamAudioDestinationNode
{-# INLINE toJSVal #-}
instance FromJSVal MediaStreamAudioDestinationNode where
fromJSVal v = fmap MediaStreamAudioDestinationNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaStreamAudioDestinationNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaStreamAudioDestinationNode where
makeObject = makeObject . unMediaStreamAudioDestinationNode
instance IsAudioNode MediaStreamAudioDestinationNode
instance IsEventTarget MediaStreamAudioDestinationNode
instance IsGObject MediaStreamAudioDestinationNode where
typeGType _ = gTypeMediaStreamAudioDestinationNode
{-# INLINE typeGType #-}
noMediaStreamAudioDestinationNode :: Maybe MediaStreamAudioDestinationNode
noMediaStreamAudioDestinationNode = Nothing
{-# INLINE noMediaStreamAudioDestinationNode #-}
gTypeMediaStreamAudioDestinationNode :: JSM GType
gTypeMediaStreamAudioDestinationNode = GType . Object <$> jsg "MediaStreamAudioDestinationNode"
newtype MediaStreamAudioSourceNode = MediaStreamAudioSourceNode { unMediaStreamAudioSourceNode :: JSVal }
instance PToJSVal MediaStreamAudioSourceNode where
pToJSVal = unMediaStreamAudioSourceNode
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaStreamAudioSourceNode where
pFromJSVal = MediaStreamAudioSourceNode
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaStreamAudioSourceNode where
toJSVal = return . unMediaStreamAudioSourceNode
{-# INLINE toJSVal #-}
instance FromJSVal MediaStreamAudioSourceNode where
fromJSVal v = fmap MediaStreamAudioSourceNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaStreamAudioSourceNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaStreamAudioSourceNode where
makeObject = makeObject . unMediaStreamAudioSourceNode
instance IsAudioNode MediaStreamAudioSourceNode
instance IsEventTarget MediaStreamAudioSourceNode
instance IsGObject MediaStreamAudioSourceNode where
typeGType _ = gTypeMediaStreamAudioSourceNode
{-# INLINE typeGType #-}
noMediaStreamAudioSourceNode :: Maybe MediaStreamAudioSourceNode
noMediaStreamAudioSourceNode = Nothing
{-# INLINE noMediaStreamAudioSourceNode #-}
gTypeMediaStreamAudioSourceNode :: JSM GType
gTypeMediaStreamAudioSourceNode = GType . Object <$> jsg "MediaStreamAudioSourceNode"
newtype MediaStreamConstraints = MediaStreamConstraints { unMediaStreamConstraints :: JSVal }
instance PToJSVal MediaStreamConstraints where
pToJSVal = unMediaStreamConstraints
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaStreamConstraints where
pFromJSVal = MediaStreamConstraints
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaStreamConstraints where
toJSVal = return . unMediaStreamConstraints
{-# INLINE toJSVal #-}
instance FromJSVal MediaStreamConstraints where
fromJSVal v = fmap MediaStreamConstraints <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaStreamConstraints
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaStreamConstraints where
makeObject = makeObject . unMediaStreamConstraints
instance IsGObject MediaStreamConstraints where
typeGType _ = gTypeMediaStreamConstraints
{-# INLINE typeGType #-}
noMediaStreamConstraints :: Maybe MediaStreamConstraints
noMediaStreamConstraints = Nothing
{-# INLINE noMediaStreamConstraints #-}
gTypeMediaStreamConstraints :: JSM GType
gTypeMediaStreamConstraints = GType . Object <$> jsg "MediaStreamConstraints"
newtype MediaStreamEvent = MediaStreamEvent { unMediaStreamEvent :: JSVal }
instance PToJSVal MediaStreamEvent where
pToJSVal = unMediaStreamEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaStreamEvent where
pFromJSVal = MediaStreamEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaStreamEvent where
toJSVal = return . unMediaStreamEvent
{-# INLINE toJSVal #-}
instance FromJSVal MediaStreamEvent where
fromJSVal v = fmap MediaStreamEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaStreamEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaStreamEvent where
makeObject = makeObject . unMediaStreamEvent
instance IsEvent MediaStreamEvent
instance IsGObject MediaStreamEvent where
typeGType _ = gTypeMediaStreamEvent
{-# INLINE typeGType #-}
noMediaStreamEvent :: Maybe MediaStreamEvent
noMediaStreamEvent = Nothing
{-# INLINE noMediaStreamEvent #-}
gTypeMediaStreamEvent :: JSM GType
gTypeMediaStreamEvent = GType . Object <$> jsg "MediaStreamEvent"
newtype MediaStreamEventInit = MediaStreamEventInit { unMediaStreamEventInit :: JSVal }
instance PToJSVal MediaStreamEventInit where
pToJSVal = unMediaStreamEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaStreamEventInit where
pFromJSVal = MediaStreamEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaStreamEventInit where
toJSVal = return . unMediaStreamEventInit
{-# INLINE toJSVal #-}
instance FromJSVal MediaStreamEventInit where
fromJSVal v = fmap MediaStreamEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaStreamEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaStreamEventInit where
makeObject = makeObject . unMediaStreamEventInit
instance IsEventInit MediaStreamEventInit
instance IsGObject MediaStreamEventInit where
typeGType _ = gTypeMediaStreamEventInit
{-# INLINE typeGType #-}
noMediaStreamEventInit :: Maybe MediaStreamEventInit
noMediaStreamEventInit = Nothing
{-# INLINE noMediaStreamEventInit #-}
gTypeMediaStreamEventInit :: JSM GType
gTypeMediaStreamEventInit = GType . Object <$> jsg "MediaStreamEventInit"
newtype MediaStreamTrack = MediaStreamTrack { unMediaStreamTrack :: JSVal }
instance PToJSVal MediaStreamTrack where
pToJSVal = unMediaStreamTrack
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaStreamTrack where
pFromJSVal = MediaStreamTrack
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaStreamTrack where
toJSVal = return . unMediaStreamTrack
{-# INLINE toJSVal #-}
instance FromJSVal MediaStreamTrack where
fromJSVal v = fmap MediaStreamTrack <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaStreamTrack
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaStreamTrack where
makeObject = makeObject . unMediaStreamTrack
class (IsEventTarget o, IsGObject o) => IsMediaStreamTrack o
toMediaStreamTrack :: IsMediaStreamTrack o => o -> MediaStreamTrack
toMediaStreamTrack = MediaStreamTrack . coerce
instance IsMediaStreamTrack MediaStreamTrack
instance IsEventTarget MediaStreamTrack
instance IsGObject MediaStreamTrack where
typeGType _ = gTypeMediaStreamTrack
{-# INLINE typeGType #-}
noMediaStreamTrack :: Maybe MediaStreamTrack
noMediaStreamTrack = Nothing
{-# INLINE noMediaStreamTrack #-}
gTypeMediaStreamTrack :: JSM GType
gTypeMediaStreamTrack = GType . Object <$> jsg "MediaStreamTrack"
newtype MediaStreamTrackEvent = MediaStreamTrackEvent { unMediaStreamTrackEvent :: JSVal }
instance PToJSVal MediaStreamTrackEvent where
pToJSVal = unMediaStreamTrackEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaStreamTrackEvent where
pFromJSVal = MediaStreamTrackEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaStreamTrackEvent where
toJSVal = return . unMediaStreamTrackEvent
{-# INLINE toJSVal #-}
instance FromJSVal MediaStreamTrackEvent where
fromJSVal v = fmap MediaStreamTrackEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaStreamTrackEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaStreamTrackEvent where
makeObject = makeObject . unMediaStreamTrackEvent
instance IsEvent MediaStreamTrackEvent
instance IsGObject MediaStreamTrackEvent where
typeGType _ = gTypeMediaStreamTrackEvent
{-# INLINE typeGType #-}
noMediaStreamTrackEvent :: Maybe MediaStreamTrackEvent
noMediaStreamTrackEvent = Nothing
{-# INLINE noMediaStreamTrackEvent #-}
gTypeMediaStreamTrackEvent :: JSM GType
gTypeMediaStreamTrackEvent = GType . Object <$> jsg "MediaStreamTrackEvent"
newtype MediaStreamTrackEventInit = MediaStreamTrackEventInit { unMediaStreamTrackEventInit :: JSVal }
instance PToJSVal MediaStreamTrackEventInit where
pToJSVal = unMediaStreamTrackEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaStreamTrackEventInit where
pFromJSVal = MediaStreamTrackEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaStreamTrackEventInit where
toJSVal = return . unMediaStreamTrackEventInit
{-# INLINE toJSVal #-}
instance FromJSVal MediaStreamTrackEventInit where
fromJSVal v = fmap MediaStreamTrackEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaStreamTrackEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaStreamTrackEventInit where
makeObject = makeObject . unMediaStreamTrackEventInit
instance IsEventInit MediaStreamTrackEventInit
instance IsGObject MediaStreamTrackEventInit where
typeGType _ = gTypeMediaStreamTrackEventInit
{-# INLINE typeGType #-}
noMediaStreamTrackEventInit :: Maybe MediaStreamTrackEventInit
noMediaStreamTrackEventInit = Nothing
{-# INLINE noMediaStreamTrackEventInit #-}
gTypeMediaStreamTrackEventInit :: JSM GType
gTypeMediaStreamTrackEventInit = GType . Object <$> jsg "MediaStreamTrackEventInit"
newtype MediaTrackCapabilities = MediaTrackCapabilities { unMediaTrackCapabilities :: JSVal }
instance PToJSVal MediaTrackCapabilities where
pToJSVal = unMediaTrackCapabilities
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaTrackCapabilities where
pFromJSVal = MediaTrackCapabilities
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaTrackCapabilities where
toJSVal = return . unMediaTrackCapabilities
{-# INLINE toJSVal #-}
instance FromJSVal MediaTrackCapabilities where
fromJSVal v = fmap MediaTrackCapabilities <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaTrackCapabilities
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaTrackCapabilities where
makeObject = makeObject . unMediaTrackCapabilities
instance IsGObject MediaTrackCapabilities where
typeGType _ = gTypeMediaTrackCapabilities
{-# INLINE typeGType #-}
noMediaTrackCapabilities :: Maybe MediaTrackCapabilities
noMediaTrackCapabilities = Nothing
{-# INLINE noMediaTrackCapabilities #-}
gTypeMediaTrackCapabilities :: JSM GType
gTypeMediaTrackCapabilities = GType . Object <$> jsg "MediaTrackCapabilities"
newtype MediaTrackConstraintSet = MediaTrackConstraintSet { unMediaTrackConstraintSet :: JSVal }
instance PToJSVal MediaTrackConstraintSet where
pToJSVal = unMediaTrackConstraintSet
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaTrackConstraintSet where
pFromJSVal = MediaTrackConstraintSet
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaTrackConstraintSet where
toJSVal = return . unMediaTrackConstraintSet
{-# INLINE toJSVal #-}
instance FromJSVal MediaTrackConstraintSet where
fromJSVal v = fmap MediaTrackConstraintSet <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaTrackConstraintSet
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaTrackConstraintSet where
makeObject = makeObject . unMediaTrackConstraintSet
class (IsGObject o) => IsMediaTrackConstraintSet o
toMediaTrackConstraintSet :: IsMediaTrackConstraintSet o => o -> MediaTrackConstraintSet
toMediaTrackConstraintSet = MediaTrackConstraintSet . coerce
instance IsMediaTrackConstraintSet MediaTrackConstraintSet
instance IsGObject MediaTrackConstraintSet where
typeGType _ = gTypeMediaTrackConstraintSet
{-# INLINE typeGType #-}
noMediaTrackConstraintSet :: Maybe MediaTrackConstraintSet
noMediaTrackConstraintSet = Nothing
{-# INLINE noMediaTrackConstraintSet #-}
gTypeMediaTrackConstraintSet :: JSM GType
gTypeMediaTrackConstraintSet = GType . Object <$> jsg "MediaTrackConstraintSet"
newtype MediaTrackConstraints = MediaTrackConstraints { unMediaTrackConstraints :: JSVal }
instance PToJSVal MediaTrackConstraints where
pToJSVal = unMediaTrackConstraints
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaTrackConstraints where
pFromJSVal = MediaTrackConstraints
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaTrackConstraints where
toJSVal = return . unMediaTrackConstraints
{-# INLINE toJSVal #-}
instance FromJSVal MediaTrackConstraints where
fromJSVal v = fmap MediaTrackConstraints <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaTrackConstraints
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaTrackConstraints where
makeObject = makeObject . unMediaTrackConstraints
instance IsMediaTrackConstraintSet MediaTrackConstraints
instance IsGObject MediaTrackConstraints where
typeGType _ = gTypeMediaTrackConstraints
{-# INLINE typeGType #-}
noMediaTrackConstraints :: Maybe MediaTrackConstraints
noMediaTrackConstraints = Nothing
{-# INLINE noMediaTrackConstraints #-}
gTypeMediaTrackConstraints :: JSM GType
gTypeMediaTrackConstraints = GType . Object <$> jsg "MediaTrackConstraints"
newtype MediaTrackSettings = MediaTrackSettings { unMediaTrackSettings :: JSVal }
instance PToJSVal MediaTrackSettings where
pToJSVal = unMediaTrackSettings
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaTrackSettings where
pFromJSVal = MediaTrackSettings
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaTrackSettings where
toJSVal = return . unMediaTrackSettings
{-# INLINE toJSVal #-}
instance FromJSVal MediaTrackSettings where
fromJSVal v = fmap MediaTrackSettings <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaTrackSettings
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaTrackSettings where
makeObject = makeObject . unMediaTrackSettings
instance IsGObject MediaTrackSettings where
typeGType _ = gTypeMediaTrackSettings
{-# INLINE typeGType #-}
noMediaTrackSettings :: Maybe MediaTrackSettings
noMediaTrackSettings = Nothing
{-# INLINE noMediaTrackSettings #-}
gTypeMediaTrackSettings :: JSM GType
gTypeMediaTrackSettings = GType . Object <$> jsg "MediaTrackSettings"
newtype MediaTrackSupportedConstraints = MediaTrackSupportedConstraints { unMediaTrackSupportedConstraints :: JSVal }
instance PToJSVal MediaTrackSupportedConstraints where
pToJSVal = unMediaTrackSupportedConstraints
{-# INLINE pToJSVal #-}
instance PFromJSVal MediaTrackSupportedConstraints where
pFromJSVal = MediaTrackSupportedConstraints
{-# INLINE pFromJSVal #-}
instance ToJSVal MediaTrackSupportedConstraints where
toJSVal = return . unMediaTrackSupportedConstraints
{-# INLINE toJSVal #-}
instance FromJSVal MediaTrackSupportedConstraints where
fromJSVal v = fmap MediaTrackSupportedConstraints <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MediaTrackSupportedConstraints
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MediaTrackSupportedConstraints where
makeObject = makeObject . unMediaTrackSupportedConstraints
instance IsGObject MediaTrackSupportedConstraints where
typeGType _ = gTypeMediaTrackSupportedConstraints
{-# INLINE typeGType #-}
noMediaTrackSupportedConstraints :: Maybe MediaTrackSupportedConstraints
noMediaTrackSupportedConstraints = Nothing
{-# INLINE noMediaTrackSupportedConstraints #-}
gTypeMediaTrackSupportedConstraints :: JSM GType
gTypeMediaTrackSupportedConstraints = GType . Object <$> jsg "MediaTrackSupportedConstraints"
newtype MessageChannel = MessageChannel { unMessageChannel :: JSVal }
instance PToJSVal MessageChannel where
pToJSVal = unMessageChannel
{-# INLINE pToJSVal #-}
instance PFromJSVal MessageChannel where
pFromJSVal = MessageChannel
{-# INLINE pFromJSVal #-}
instance ToJSVal MessageChannel where
toJSVal = return . unMessageChannel
{-# INLINE toJSVal #-}
instance FromJSVal MessageChannel where
fromJSVal v = fmap MessageChannel <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MessageChannel
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MessageChannel where
makeObject = makeObject . unMessageChannel
instance IsGObject MessageChannel where
typeGType _ = gTypeMessageChannel
{-# INLINE typeGType #-}
noMessageChannel :: Maybe MessageChannel
noMessageChannel = Nothing
{-# INLINE noMessageChannel #-}
gTypeMessageChannel :: JSM GType
gTypeMessageChannel = GType . Object <$> jsg "MessageChannel"
newtype MessageEvent = MessageEvent { unMessageEvent :: JSVal }
instance PToJSVal MessageEvent where
pToJSVal = unMessageEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal MessageEvent where
pFromJSVal = MessageEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal MessageEvent where
toJSVal = return . unMessageEvent
{-# INLINE toJSVal #-}
instance FromJSVal MessageEvent where
fromJSVal v = fmap MessageEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MessageEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MessageEvent where
makeObject = makeObject . unMessageEvent
instance IsEvent MessageEvent
instance IsGObject MessageEvent where
typeGType _ = gTypeMessageEvent
{-# INLINE typeGType #-}
noMessageEvent :: Maybe MessageEvent
noMessageEvent = Nothing
{-# INLINE noMessageEvent #-}
gTypeMessageEvent :: JSM GType
gTypeMessageEvent = GType . Object <$> jsg "MessageEvent"
newtype MessageEventInit = MessageEventInit { unMessageEventInit :: JSVal }
instance PToJSVal MessageEventInit where
pToJSVal = unMessageEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal MessageEventInit where
pFromJSVal = MessageEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal MessageEventInit where
toJSVal = return . unMessageEventInit
{-# INLINE toJSVal #-}
instance FromJSVal MessageEventInit where
fromJSVal v = fmap MessageEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MessageEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MessageEventInit where
makeObject = makeObject . unMessageEventInit
instance IsEventInit MessageEventInit
instance IsGObject MessageEventInit where
typeGType _ = gTypeMessageEventInit
{-# INLINE typeGType #-}
noMessageEventInit :: Maybe MessageEventInit
noMessageEventInit = Nothing
{-# INLINE noMessageEventInit #-}
gTypeMessageEventInit :: JSM GType
gTypeMessageEventInit = GType . Object <$> jsg "MessageEventInit"
newtype MessagePort = MessagePort { unMessagePort :: JSVal }
instance PToJSVal MessagePort where
pToJSVal = unMessagePort
{-# INLINE pToJSVal #-}
instance PFromJSVal MessagePort where
pFromJSVal = MessagePort
{-# INLINE pFromJSVal #-}
instance ToJSVal MessagePort where
toJSVal = return . unMessagePort
{-# INLINE toJSVal #-}
instance FromJSVal MessagePort where
fromJSVal v = fmap MessagePort <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MessagePort
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MessagePort where
makeObject = makeObject . unMessagePort
instance IsEventTarget MessagePort
instance IsGObject MessagePort where
typeGType _ = gTypeMessagePort
{-# INLINE typeGType #-}
noMessagePort :: Maybe MessagePort
noMessagePort = Nothing
{-# INLINE noMessagePort #-}
gTypeMessagePort :: JSM GType
gTypeMessagePort = GType . Object <$> jsg "MessagePort"
newtype MimeType = MimeType { unMimeType :: JSVal }
instance PToJSVal MimeType where
pToJSVal = unMimeType
{-# INLINE pToJSVal #-}
instance PFromJSVal MimeType where
pFromJSVal = MimeType
{-# INLINE pFromJSVal #-}
instance ToJSVal MimeType where
toJSVal = return . unMimeType
{-# INLINE toJSVal #-}
instance FromJSVal MimeType where
fromJSVal v = fmap MimeType <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MimeType
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MimeType where
makeObject = makeObject . unMimeType
instance IsGObject MimeType where
typeGType _ = gTypeMimeType
{-# INLINE typeGType #-}
noMimeType :: Maybe MimeType
noMimeType = Nothing
{-# INLINE noMimeType #-}
gTypeMimeType :: JSM GType
gTypeMimeType = GType . Object <$> jsg "MimeType"
newtype MimeTypeArray = MimeTypeArray { unMimeTypeArray :: JSVal }
instance PToJSVal MimeTypeArray where
pToJSVal = unMimeTypeArray
{-# INLINE pToJSVal #-}
instance PFromJSVal MimeTypeArray where
pFromJSVal = MimeTypeArray
{-# INLINE pFromJSVal #-}
instance ToJSVal MimeTypeArray where
toJSVal = return . unMimeTypeArray
{-# INLINE toJSVal #-}
instance FromJSVal MimeTypeArray where
fromJSVal v = fmap MimeTypeArray <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MimeTypeArray
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MimeTypeArray where
makeObject = makeObject . unMimeTypeArray
instance IsGObject MimeTypeArray where
typeGType _ = gTypeMimeTypeArray
{-# INLINE typeGType #-}
noMimeTypeArray :: Maybe MimeTypeArray
noMimeTypeArray = Nothing
{-# INLINE noMimeTypeArray #-}
gTypeMimeTypeArray :: JSM GType
gTypeMimeTypeArray = GType . Object <$> jsg "MimeTypeArray"
newtype MouseEvent = MouseEvent { unMouseEvent :: JSVal }
instance PToJSVal MouseEvent where
pToJSVal = unMouseEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal MouseEvent where
pFromJSVal = MouseEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal MouseEvent where
toJSVal = return . unMouseEvent
{-# INLINE toJSVal #-}
instance FromJSVal MouseEvent where
fromJSVal v = fmap MouseEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MouseEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MouseEvent where
makeObject = makeObject . unMouseEvent
class (IsUIEvent o, IsEvent o, IsGObject o) => IsMouseEvent o
toMouseEvent :: IsMouseEvent o => o -> MouseEvent
toMouseEvent = MouseEvent . coerce
instance IsMouseEvent MouseEvent
instance IsUIEvent MouseEvent
instance IsEvent MouseEvent
instance IsGObject MouseEvent where
typeGType _ = gTypeMouseEvent
{-# INLINE typeGType #-}
noMouseEvent :: Maybe MouseEvent
noMouseEvent = Nothing
{-# INLINE noMouseEvent #-}
gTypeMouseEvent :: JSM GType
gTypeMouseEvent = GType . Object <$> jsg "MouseEvent"
newtype MouseEventInit = MouseEventInit { unMouseEventInit :: JSVal }
instance PToJSVal MouseEventInit where
pToJSVal = unMouseEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal MouseEventInit where
pFromJSVal = MouseEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal MouseEventInit where
toJSVal = return . unMouseEventInit
{-# INLINE toJSVal #-}
instance FromJSVal MouseEventInit where
fromJSVal v = fmap MouseEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MouseEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MouseEventInit where
makeObject = makeObject . unMouseEventInit
class (IsEventModifierInit o, IsUIEventInit o, IsEventInit o, IsGObject o) => IsMouseEventInit o
toMouseEventInit :: IsMouseEventInit o => o -> MouseEventInit
toMouseEventInit = MouseEventInit . coerce
instance IsMouseEventInit MouseEventInit
instance IsEventModifierInit MouseEventInit
instance IsUIEventInit MouseEventInit
instance IsEventInit MouseEventInit
instance IsGObject MouseEventInit where
typeGType _ = gTypeMouseEventInit
{-# INLINE typeGType #-}
noMouseEventInit :: Maybe MouseEventInit
noMouseEventInit = Nothing
{-# INLINE noMouseEventInit #-}
gTypeMouseEventInit :: JSM GType
gTypeMouseEventInit = GType . Object <$> jsg "MouseEventInit"
newtype MutationEvent = MutationEvent { unMutationEvent :: JSVal }
instance PToJSVal MutationEvent where
pToJSVal = unMutationEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal MutationEvent where
pFromJSVal = MutationEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal MutationEvent where
toJSVal = return . unMutationEvent
{-# INLINE toJSVal #-}
instance FromJSVal MutationEvent where
fromJSVal v = fmap MutationEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MutationEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MutationEvent where
makeObject = makeObject . unMutationEvent
instance IsEvent MutationEvent
instance IsGObject MutationEvent where
typeGType _ = gTypeMutationEvent
{-# INLINE typeGType #-}
noMutationEvent :: Maybe MutationEvent
noMutationEvent = Nothing
{-# INLINE noMutationEvent #-}
gTypeMutationEvent :: JSM GType
gTypeMutationEvent = GType . Object <$> jsg "MutationEvent"
newtype MutationObserver = MutationObserver { unMutationObserver :: JSVal }
instance PToJSVal MutationObserver where
pToJSVal = unMutationObserver
{-# INLINE pToJSVal #-}
instance PFromJSVal MutationObserver where
pFromJSVal = MutationObserver
{-# INLINE pFromJSVal #-}
instance ToJSVal MutationObserver where
toJSVal = return . unMutationObserver
{-# INLINE toJSVal #-}
instance FromJSVal MutationObserver where
fromJSVal v = fmap MutationObserver <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MutationObserver
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MutationObserver where
makeObject = makeObject . unMutationObserver
instance IsGObject MutationObserver where
typeGType _ = gTypeMutationObserver
{-# INLINE typeGType #-}
noMutationObserver :: Maybe MutationObserver
noMutationObserver = Nothing
{-# INLINE noMutationObserver #-}
gTypeMutationObserver :: JSM GType
gTypeMutationObserver = GType . Object <$> jsg "MutationObserver"
newtype MutationObserverInit = MutationObserverInit { unMutationObserverInit :: JSVal }
instance PToJSVal MutationObserverInit where
pToJSVal = unMutationObserverInit
{-# INLINE pToJSVal #-}
instance PFromJSVal MutationObserverInit where
pFromJSVal = MutationObserverInit
{-# INLINE pFromJSVal #-}
instance ToJSVal MutationObserverInit where
toJSVal = return . unMutationObserverInit
{-# INLINE toJSVal #-}
instance FromJSVal MutationObserverInit where
fromJSVal v = fmap MutationObserverInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MutationObserverInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MutationObserverInit where
makeObject = makeObject . unMutationObserverInit
instance IsGObject MutationObserverInit where
typeGType _ = gTypeMutationObserverInit
{-# INLINE typeGType #-}
noMutationObserverInit :: Maybe MutationObserverInit
noMutationObserverInit = Nothing
{-# INLINE noMutationObserverInit #-}
gTypeMutationObserverInit :: JSM GType
gTypeMutationObserverInit = GType . Object <$> jsg "MutationObserverInit"
newtype MutationRecord = MutationRecord { unMutationRecord :: JSVal }
instance PToJSVal MutationRecord where
pToJSVal = unMutationRecord
{-# INLINE pToJSVal #-}
instance PFromJSVal MutationRecord where
pFromJSVal = MutationRecord
{-# INLINE pFromJSVal #-}
instance ToJSVal MutationRecord where
toJSVal = return . unMutationRecord
{-# INLINE toJSVal #-}
instance FromJSVal MutationRecord where
fromJSVal v = fmap MutationRecord <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . MutationRecord
{-# INLINE fromJSValUnchecked #-}
instance MakeObject MutationRecord where
makeObject = makeObject . unMutationRecord
instance IsGObject MutationRecord where
typeGType _ = gTypeMutationRecord
{-# INLINE typeGType #-}
noMutationRecord :: Maybe MutationRecord
noMutationRecord = Nothing
{-# INLINE noMutationRecord #-}
gTypeMutationRecord :: JSM GType
gTypeMutationRecord = GType . Object <$> jsg "MutationRecord"
newtype NamedNodeMap = NamedNodeMap { unNamedNodeMap :: JSVal }
instance PToJSVal NamedNodeMap where
pToJSVal = unNamedNodeMap
{-# INLINE pToJSVal #-}
instance PFromJSVal NamedNodeMap where
pFromJSVal = NamedNodeMap
{-# INLINE pFromJSVal #-}
instance ToJSVal NamedNodeMap where
toJSVal = return . unNamedNodeMap
{-# INLINE toJSVal #-}
instance FromJSVal NamedNodeMap where
fromJSVal v = fmap NamedNodeMap <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NamedNodeMap
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NamedNodeMap where
makeObject = makeObject . unNamedNodeMap
instance IsGObject NamedNodeMap where
typeGType _ = gTypeNamedNodeMap
{-# INLINE typeGType #-}
noNamedNodeMap :: Maybe NamedNodeMap
noNamedNodeMap = Nothing
{-# INLINE noNamedNodeMap #-}
gTypeNamedNodeMap :: JSM GType
gTypeNamedNodeMap = GType . Object <$> jsg "NamedNodeMap"
newtype Navigator = Navigator { unNavigator :: JSVal }
instance PToJSVal Navigator where
pToJSVal = unNavigator
{-# INLINE pToJSVal #-}
instance PFromJSVal Navigator where
pFromJSVal = Navigator
{-# INLINE pFromJSVal #-}
instance ToJSVal Navigator where
toJSVal = return . unNavigator
{-# INLINE toJSVal #-}
instance FromJSVal Navigator where
fromJSVal v = fmap Navigator <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Navigator
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Navigator where
makeObject = makeObject . unNavigator
instance IsNavigatorOnLine Navigator
instance IsNavigatorLanguage Navigator
instance IsNavigatorID Navigator
instance IsNavigatorConcurrentHardware Navigator
instance IsGObject Navigator where
typeGType _ = gTypeNavigator
{-# INLINE typeGType #-}
noNavigator :: Maybe Navigator
noNavigator = Nothing
{-# INLINE noNavigator #-}
gTypeNavigator :: JSM GType
gTypeNavigator = GType . Object <$> jsg "Navigator"
newtype NavigatorConcurrentHardware = NavigatorConcurrentHardware { unNavigatorConcurrentHardware :: JSVal }
instance PToJSVal NavigatorConcurrentHardware where
pToJSVal = unNavigatorConcurrentHardware
{-# INLINE pToJSVal #-}
instance PFromJSVal NavigatorConcurrentHardware where
pFromJSVal = NavigatorConcurrentHardware
{-# INLINE pFromJSVal #-}
instance ToJSVal NavigatorConcurrentHardware where
toJSVal = return . unNavigatorConcurrentHardware
{-# INLINE toJSVal #-}
instance FromJSVal NavigatorConcurrentHardware where
fromJSVal v = fmap NavigatorConcurrentHardware <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NavigatorConcurrentHardware
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NavigatorConcurrentHardware where
makeObject = makeObject . unNavigatorConcurrentHardware
class (IsGObject o) => IsNavigatorConcurrentHardware o
toNavigatorConcurrentHardware :: IsNavigatorConcurrentHardware o => o -> NavigatorConcurrentHardware
toNavigatorConcurrentHardware = NavigatorConcurrentHardware . coerce
instance IsNavigatorConcurrentHardware NavigatorConcurrentHardware
instance IsGObject NavigatorConcurrentHardware where
typeGType _ = gTypeNavigatorConcurrentHardware
{-# INLINE typeGType #-}
noNavigatorConcurrentHardware :: Maybe NavigatorConcurrentHardware
noNavigatorConcurrentHardware = Nothing
{-# INLINE noNavigatorConcurrentHardware #-}
gTypeNavigatorConcurrentHardware :: JSM GType
gTypeNavigatorConcurrentHardware = GType . Object <$> jsg "NavigatorConcurrentHardware"
newtype NavigatorID = NavigatorID { unNavigatorID :: JSVal }
instance PToJSVal NavigatorID where
pToJSVal = unNavigatorID
{-# INLINE pToJSVal #-}
instance PFromJSVal NavigatorID where
pFromJSVal = NavigatorID
{-# INLINE pFromJSVal #-}
instance ToJSVal NavigatorID where
toJSVal = return . unNavigatorID
{-# INLINE toJSVal #-}
instance FromJSVal NavigatorID where
fromJSVal v = fmap NavigatorID <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NavigatorID
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NavigatorID where
makeObject = makeObject . unNavigatorID
class (IsGObject o) => IsNavigatorID o
toNavigatorID :: IsNavigatorID o => o -> NavigatorID
toNavigatorID = NavigatorID . coerce
instance IsNavigatorID NavigatorID
instance IsGObject NavigatorID where
typeGType _ = gTypeNavigatorID
{-# INLINE typeGType #-}
noNavigatorID :: Maybe NavigatorID
noNavigatorID = Nothing
{-# INLINE noNavigatorID #-}
gTypeNavigatorID :: JSM GType
gTypeNavigatorID = GType . Object <$> jsg "NavigatorID"
newtype NavigatorLanguage = NavigatorLanguage { unNavigatorLanguage :: JSVal }
instance PToJSVal NavigatorLanguage where
pToJSVal = unNavigatorLanguage
{-# INLINE pToJSVal #-}
instance PFromJSVal NavigatorLanguage where
pFromJSVal = NavigatorLanguage
{-# INLINE pFromJSVal #-}
instance ToJSVal NavigatorLanguage where
toJSVal = return . unNavigatorLanguage
{-# INLINE toJSVal #-}
instance FromJSVal NavigatorLanguage where
fromJSVal v = fmap NavigatorLanguage <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NavigatorLanguage
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NavigatorLanguage where
makeObject = makeObject . unNavigatorLanguage
class (IsGObject o) => IsNavigatorLanguage o
toNavigatorLanguage :: IsNavigatorLanguage o => o -> NavigatorLanguage
toNavigatorLanguage = NavigatorLanguage . coerce
instance IsNavigatorLanguage NavigatorLanguage
instance IsGObject NavigatorLanguage where
typeGType _ = gTypeNavigatorLanguage
{-# INLINE typeGType #-}
noNavigatorLanguage :: Maybe NavigatorLanguage
noNavigatorLanguage = Nothing
{-# INLINE noNavigatorLanguage #-}
gTypeNavigatorLanguage :: JSM GType
gTypeNavigatorLanguage = GType . Object <$> jsg "NavigatorLanguage"
newtype NavigatorOnLine = NavigatorOnLine { unNavigatorOnLine :: JSVal }
instance PToJSVal NavigatorOnLine where
pToJSVal = unNavigatorOnLine
{-# INLINE pToJSVal #-}
instance PFromJSVal NavigatorOnLine where
pFromJSVal = NavigatorOnLine
{-# INLINE pFromJSVal #-}
instance ToJSVal NavigatorOnLine where
toJSVal = return . unNavigatorOnLine
{-# INLINE toJSVal #-}
instance FromJSVal NavigatorOnLine where
fromJSVal v = fmap NavigatorOnLine <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NavigatorOnLine
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NavigatorOnLine where
makeObject = makeObject . unNavigatorOnLine
class (IsGObject o) => IsNavigatorOnLine o
toNavigatorOnLine :: IsNavigatorOnLine o => o -> NavigatorOnLine
toNavigatorOnLine = NavigatorOnLine . coerce
instance IsNavigatorOnLine NavigatorOnLine
instance IsGObject NavigatorOnLine where
typeGType _ = gTypeNavigatorOnLine
{-# INLINE typeGType #-}
noNavigatorOnLine :: Maybe NavigatorOnLine
noNavigatorOnLine = Nothing
{-# INLINE noNavigatorOnLine #-}
gTypeNavigatorOnLine :: JSM GType
gTypeNavigatorOnLine = GType . Object <$> jsg "NavigatorOnLine"
newtype NavigatorUserMediaError = NavigatorUserMediaError { unNavigatorUserMediaError :: JSVal }
instance PToJSVal NavigatorUserMediaError where
pToJSVal = unNavigatorUserMediaError
{-# INLINE pToJSVal #-}
instance PFromJSVal NavigatorUserMediaError where
pFromJSVal = NavigatorUserMediaError
{-# INLINE pFromJSVal #-}
instance ToJSVal NavigatorUserMediaError where
toJSVal = return . unNavigatorUserMediaError
{-# INLINE toJSVal #-}
instance FromJSVal NavigatorUserMediaError where
fromJSVal v = fmap NavigatorUserMediaError <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NavigatorUserMediaError
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NavigatorUserMediaError where
makeObject = makeObject . unNavigatorUserMediaError
instance IsDOMError NavigatorUserMediaError
instance IsGObject NavigatorUserMediaError where
typeGType _ = gTypeNavigatorUserMediaError
{-# INLINE typeGType #-}
noNavigatorUserMediaError :: Maybe NavigatorUserMediaError
noNavigatorUserMediaError = Nothing
{-# INLINE noNavigatorUserMediaError #-}
gTypeNavigatorUserMediaError :: JSM GType
gTypeNavigatorUserMediaError = GType . Object <$> jsg "NavigatorUserMediaError"
newtype Node = Node { unNode :: JSVal }
instance PToJSVal Node where
pToJSVal = unNode
{-# INLINE pToJSVal #-}
instance PFromJSVal Node where
pFromJSVal = Node
{-# INLINE pFromJSVal #-}
instance ToJSVal Node where
toJSVal = return . unNode
{-# INLINE toJSVal #-}
instance FromJSVal Node where
fromJSVal v = fmap Node <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Node
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Node where
makeObject = makeObject . unNode
class (IsEventTarget o, IsGObject o) => IsNode o
toNode :: IsNode o => o -> Node
toNode = Node . coerce
instance IsNode Node
instance IsEventTarget Node
instance IsGObject Node where
typeGType _ = gTypeNode
{-# INLINE typeGType #-}
noNode :: Maybe Node
noNode = Nothing
{-# INLINE noNode #-}
gTypeNode :: JSM GType
gTypeNode = GType . Object <$> jsg "Node"
newtype NodeIterator = NodeIterator { unNodeIterator :: JSVal }
instance PToJSVal NodeIterator where
pToJSVal = unNodeIterator
{-# INLINE pToJSVal #-}
instance PFromJSVal NodeIterator where
pFromJSVal = NodeIterator
{-# INLINE pFromJSVal #-}
instance ToJSVal NodeIterator where
toJSVal = return . unNodeIterator
{-# INLINE toJSVal #-}
instance FromJSVal NodeIterator where
fromJSVal v = fmap NodeIterator <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NodeIterator
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NodeIterator where
makeObject = makeObject . unNodeIterator
instance IsGObject NodeIterator where
typeGType _ = gTypeNodeIterator
{-# INLINE typeGType #-}
noNodeIterator :: Maybe NodeIterator
noNodeIterator = Nothing
{-# INLINE noNodeIterator #-}
gTypeNodeIterator :: JSM GType
gTypeNodeIterator = GType . Object <$> jsg "NodeIterator"
newtype NodeList = NodeList { unNodeList :: JSVal }
instance PToJSVal NodeList where
pToJSVal = unNodeList
{-# INLINE pToJSVal #-}
instance PFromJSVal NodeList where
pFromJSVal = NodeList
{-# INLINE pFromJSVal #-}
instance ToJSVal NodeList where
toJSVal = return . unNodeList
{-# INLINE toJSVal #-}
instance FromJSVal NodeList where
fromJSVal v = fmap NodeList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NodeList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NodeList where
makeObject = makeObject . unNodeList
class (IsGObject o) => IsNodeList o
toNodeList :: IsNodeList o => o -> NodeList
toNodeList = NodeList . coerce
instance IsNodeList NodeList
instance IsGObject NodeList where
typeGType _ = gTypeNodeList
{-# INLINE typeGType #-}
noNodeList :: Maybe NodeList
noNodeList = Nothing
{-# INLINE noNodeList #-}
gTypeNodeList :: JSM GType
gTypeNodeList = GType . Object <$> jsg "NodeList"
newtype NonDocumentTypeChildNode = NonDocumentTypeChildNode { unNonDocumentTypeChildNode :: JSVal }
instance PToJSVal NonDocumentTypeChildNode where
pToJSVal = unNonDocumentTypeChildNode
{-# INLINE pToJSVal #-}
instance PFromJSVal NonDocumentTypeChildNode where
pFromJSVal = NonDocumentTypeChildNode
{-# INLINE pFromJSVal #-}
instance ToJSVal NonDocumentTypeChildNode where
toJSVal = return . unNonDocumentTypeChildNode
{-# INLINE toJSVal #-}
instance FromJSVal NonDocumentTypeChildNode where
fromJSVal v = fmap NonDocumentTypeChildNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NonDocumentTypeChildNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NonDocumentTypeChildNode where
makeObject = makeObject . unNonDocumentTypeChildNode
class (IsGObject o) => IsNonDocumentTypeChildNode o
toNonDocumentTypeChildNode :: IsNonDocumentTypeChildNode o => o -> NonDocumentTypeChildNode
toNonDocumentTypeChildNode = NonDocumentTypeChildNode . coerce
instance IsNonDocumentTypeChildNode NonDocumentTypeChildNode
instance IsGObject NonDocumentTypeChildNode where
typeGType _ = gTypeNonDocumentTypeChildNode
{-# INLINE typeGType #-}
noNonDocumentTypeChildNode :: Maybe NonDocumentTypeChildNode
noNonDocumentTypeChildNode = Nothing
{-# INLINE noNonDocumentTypeChildNode #-}
gTypeNonDocumentTypeChildNode :: JSM GType
gTypeNonDocumentTypeChildNode = GType . Object <$> jsg "NonDocumentTypeChildNode"
newtype NonElementParentNode = NonElementParentNode { unNonElementParentNode :: JSVal }
instance PToJSVal NonElementParentNode where
pToJSVal = unNonElementParentNode
{-# INLINE pToJSVal #-}
instance PFromJSVal NonElementParentNode where
pFromJSVal = NonElementParentNode
{-# INLINE pFromJSVal #-}
instance ToJSVal NonElementParentNode where
toJSVal = return . unNonElementParentNode
{-# INLINE toJSVal #-}
instance FromJSVal NonElementParentNode where
fromJSVal v = fmap NonElementParentNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NonElementParentNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NonElementParentNode where
makeObject = makeObject . unNonElementParentNode
class (IsGObject o) => IsNonElementParentNode o
toNonElementParentNode :: IsNonElementParentNode o => o -> NonElementParentNode
toNonElementParentNode = NonElementParentNode . coerce
instance IsNonElementParentNode NonElementParentNode
instance IsGObject NonElementParentNode where
typeGType _ = gTypeNonElementParentNode
{-# INLINE typeGType #-}
noNonElementParentNode :: Maybe NonElementParentNode
noNonElementParentNode = Nothing
{-# INLINE noNonElementParentNode #-}
gTypeNonElementParentNode :: JSM GType
gTypeNonElementParentNode = GType . Object <$> jsg "NonElementParentNode"
newtype Notification = Notification { unNotification :: JSVal }
instance PToJSVal Notification where
pToJSVal = unNotification
{-# INLINE pToJSVal #-}
instance PFromJSVal Notification where
pFromJSVal = Notification
{-# INLINE pFromJSVal #-}
instance ToJSVal Notification where
toJSVal = return . unNotification
{-# INLINE toJSVal #-}
instance FromJSVal Notification where
fromJSVal v = fmap Notification <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Notification
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Notification where
makeObject = makeObject . unNotification
instance IsEventTarget Notification
instance IsGObject Notification where
typeGType _ = gTypeNotification
{-# INLINE typeGType #-}
noNotification :: Maybe Notification
noNotification = Nothing
{-# INLINE noNotification #-}
gTypeNotification :: JSM GType
gTypeNotification = GType . Object <$> jsg "Notification"
newtype NotificationOptions = NotificationOptions { unNotificationOptions :: JSVal }
instance PToJSVal NotificationOptions where
pToJSVal = unNotificationOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal NotificationOptions where
pFromJSVal = NotificationOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal NotificationOptions where
toJSVal = return . unNotificationOptions
{-# INLINE toJSVal #-}
instance FromJSVal NotificationOptions where
fromJSVal v = fmap NotificationOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . NotificationOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject NotificationOptions where
makeObject = makeObject . unNotificationOptions
instance IsGObject NotificationOptions where
typeGType _ = gTypeNotificationOptions
{-# INLINE typeGType #-}
noNotificationOptions :: Maybe NotificationOptions
noNotificationOptions = Nothing
{-# INLINE noNotificationOptions #-}
gTypeNotificationOptions :: JSM GType
gTypeNotificationOptions = GType . Object <$> jsg "NotificationOptions"
newtype OESElementIndexUint = OESElementIndexUint { unOESElementIndexUint :: JSVal }
instance PToJSVal OESElementIndexUint where
pToJSVal = unOESElementIndexUint
{-# INLINE pToJSVal #-}
instance PFromJSVal OESElementIndexUint where
pFromJSVal = OESElementIndexUint
{-# INLINE pFromJSVal #-}
instance ToJSVal OESElementIndexUint where
toJSVal = return . unOESElementIndexUint
{-# INLINE toJSVal #-}
instance FromJSVal OESElementIndexUint where
fromJSVal v = fmap OESElementIndexUint <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OESElementIndexUint
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OESElementIndexUint where
makeObject = makeObject . unOESElementIndexUint
instance IsGObject OESElementIndexUint where
typeGType _ = gTypeOESElementIndexUint
{-# INLINE typeGType #-}
noOESElementIndexUint :: Maybe OESElementIndexUint
noOESElementIndexUint = Nothing
{-# INLINE noOESElementIndexUint #-}
gTypeOESElementIndexUint :: JSM GType
gTypeOESElementIndexUint = GType . Object <$> jsg "OESElementIndexUint"
newtype OESStandardDerivatives = OESStandardDerivatives { unOESStandardDerivatives :: JSVal }
instance PToJSVal OESStandardDerivatives where
pToJSVal = unOESStandardDerivatives
{-# INLINE pToJSVal #-}
instance PFromJSVal OESStandardDerivatives where
pFromJSVal = OESStandardDerivatives
{-# INLINE pFromJSVal #-}
instance ToJSVal OESStandardDerivatives where
toJSVal = return . unOESStandardDerivatives
{-# INLINE toJSVal #-}
instance FromJSVal OESStandardDerivatives where
fromJSVal v = fmap OESStandardDerivatives <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OESStandardDerivatives
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OESStandardDerivatives where
makeObject = makeObject . unOESStandardDerivatives
instance IsGObject OESStandardDerivatives where
typeGType _ = gTypeOESStandardDerivatives
{-# INLINE typeGType #-}
noOESStandardDerivatives :: Maybe OESStandardDerivatives
noOESStandardDerivatives = Nothing
{-# INLINE noOESStandardDerivatives #-}
gTypeOESStandardDerivatives :: JSM GType
gTypeOESStandardDerivatives = GType . Object <$> jsg "OESStandardDerivatives"
newtype OESTextureFloat = OESTextureFloat { unOESTextureFloat :: JSVal }
instance PToJSVal OESTextureFloat where
pToJSVal = unOESTextureFloat
{-# INLINE pToJSVal #-}
instance PFromJSVal OESTextureFloat where
pFromJSVal = OESTextureFloat
{-# INLINE pFromJSVal #-}
instance ToJSVal OESTextureFloat where
toJSVal = return . unOESTextureFloat
{-# INLINE toJSVal #-}
instance FromJSVal OESTextureFloat where
fromJSVal v = fmap OESTextureFloat <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OESTextureFloat
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OESTextureFloat where
makeObject = makeObject . unOESTextureFloat
instance IsGObject OESTextureFloat where
typeGType _ = gTypeOESTextureFloat
{-# INLINE typeGType #-}
noOESTextureFloat :: Maybe OESTextureFloat
noOESTextureFloat = Nothing
{-# INLINE noOESTextureFloat #-}
gTypeOESTextureFloat :: JSM GType
gTypeOESTextureFloat = GType . Object <$> jsg "OESTextureFloat"
newtype OESTextureFloatLinear = OESTextureFloatLinear { unOESTextureFloatLinear :: JSVal }
instance PToJSVal OESTextureFloatLinear where
pToJSVal = unOESTextureFloatLinear
{-# INLINE pToJSVal #-}
instance PFromJSVal OESTextureFloatLinear where
pFromJSVal = OESTextureFloatLinear
{-# INLINE pFromJSVal #-}
instance ToJSVal OESTextureFloatLinear where
toJSVal = return . unOESTextureFloatLinear
{-# INLINE toJSVal #-}
instance FromJSVal OESTextureFloatLinear where
fromJSVal v = fmap OESTextureFloatLinear <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OESTextureFloatLinear
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OESTextureFloatLinear where
makeObject = makeObject . unOESTextureFloatLinear
instance IsGObject OESTextureFloatLinear where
typeGType _ = gTypeOESTextureFloatLinear
{-# INLINE typeGType #-}
noOESTextureFloatLinear :: Maybe OESTextureFloatLinear
noOESTextureFloatLinear = Nothing
{-# INLINE noOESTextureFloatLinear #-}
gTypeOESTextureFloatLinear :: JSM GType
gTypeOESTextureFloatLinear = GType . Object <$> jsg "OESTextureFloatLinear"
newtype OESTextureHalfFloat = OESTextureHalfFloat { unOESTextureHalfFloat :: JSVal }
instance PToJSVal OESTextureHalfFloat where
pToJSVal = unOESTextureHalfFloat
{-# INLINE pToJSVal #-}
instance PFromJSVal OESTextureHalfFloat where
pFromJSVal = OESTextureHalfFloat
{-# INLINE pFromJSVal #-}
instance ToJSVal OESTextureHalfFloat where
toJSVal = return . unOESTextureHalfFloat
{-# INLINE toJSVal #-}
instance FromJSVal OESTextureHalfFloat where
fromJSVal v = fmap OESTextureHalfFloat <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OESTextureHalfFloat
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OESTextureHalfFloat where
makeObject = makeObject . unOESTextureHalfFloat
instance IsGObject OESTextureHalfFloat where
typeGType _ = gTypeOESTextureHalfFloat
{-# INLINE typeGType #-}
noOESTextureHalfFloat :: Maybe OESTextureHalfFloat
noOESTextureHalfFloat = Nothing
{-# INLINE noOESTextureHalfFloat #-}
gTypeOESTextureHalfFloat :: JSM GType
gTypeOESTextureHalfFloat = GType . Object <$> jsg "OESTextureHalfFloat"
newtype OESTextureHalfFloatLinear = OESTextureHalfFloatLinear { unOESTextureHalfFloatLinear :: JSVal }
instance PToJSVal OESTextureHalfFloatLinear where
pToJSVal = unOESTextureHalfFloatLinear
{-# INLINE pToJSVal #-}
instance PFromJSVal OESTextureHalfFloatLinear where
pFromJSVal = OESTextureHalfFloatLinear
{-# INLINE pFromJSVal #-}
instance ToJSVal OESTextureHalfFloatLinear where
toJSVal = return . unOESTextureHalfFloatLinear
{-# INLINE toJSVal #-}
instance FromJSVal OESTextureHalfFloatLinear where
fromJSVal v = fmap OESTextureHalfFloatLinear <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OESTextureHalfFloatLinear
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OESTextureHalfFloatLinear where
makeObject = makeObject . unOESTextureHalfFloatLinear
instance IsGObject OESTextureHalfFloatLinear where
typeGType _ = gTypeOESTextureHalfFloatLinear
{-# INLINE typeGType #-}
noOESTextureHalfFloatLinear :: Maybe OESTextureHalfFloatLinear
noOESTextureHalfFloatLinear = Nothing
{-# INLINE noOESTextureHalfFloatLinear #-}
gTypeOESTextureHalfFloatLinear :: JSM GType
gTypeOESTextureHalfFloatLinear = GType . Object <$> jsg "OESTextureHalfFloatLinear"
newtype OESVertexArrayObject = OESVertexArrayObject { unOESVertexArrayObject :: JSVal }
instance PToJSVal OESVertexArrayObject where
pToJSVal = unOESVertexArrayObject
{-# INLINE pToJSVal #-}
instance PFromJSVal OESVertexArrayObject where
pFromJSVal = OESVertexArrayObject
{-# INLINE pFromJSVal #-}
instance ToJSVal OESVertexArrayObject where
toJSVal = return . unOESVertexArrayObject
{-# INLINE toJSVal #-}
instance FromJSVal OESVertexArrayObject where
fromJSVal v = fmap OESVertexArrayObject <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OESVertexArrayObject
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OESVertexArrayObject where
makeObject = makeObject . unOESVertexArrayObject
instance IsGObject OESVertexArrayObject where
typeGType _ = gTypeOESVertexArrayObject
{-# INLINE typeGType #-}
noOESVertexArrayObject :: Maybe OESVertexArrayObject
noOESVertexArrayObject = Nothing
{-# INLINE noOESVertexArrayObject #-}
gTypeOESVertexArrayObject :: JSM GType
gTypeOESVertexArrayObject = GType . Object <$> jsg "OESVertexArrayObject"
newtype OfflineAudioCompletionEvent = OfflineAudioCompletionEvent { unOfflineAudioCompletionEvent :: JSVal }
instance PToJSVal OfflineAudioCompletionEvent where
pToJSVal = unOfflineAudioCompletionEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal OfflineAudioCompletionEvent where
pFromJSVal = OfflineAudioCompletionEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal OfflineAudioCompletionEvent where
toJSVal = return . unOfflineAudioCompletionEvent
{-# INLINE toJSVal #-}
instance FromJSVal OfflineAudioCompletionEvent where
fromJSVal v = fmap OfflineAudioCompletionEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OfflineAudioCompletionEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OfflineAudioCompletionEvent where
makeObject = makeObject . unOfflineAudioCompletionEvent
instance IsEvent OfflineAudioCompletionEvent
instance IsGObject OfflineAudioCompletionEvent where
typeGType _ = gTypeOfflineAudioCompletionEvent
{-# INLINE typeGType #-}
noOfflineAudioCompletionEvent :: Maybe OfflineAudioCompletionEvent
noOfflineAudioCompletionEvent = Nothing
{-# INLINE noOfflineAudioCompletionEvent #-}
gTypeOfflineAudioCompletionEvent :: JSM GType
gTypeOfflineAudioCompletionEvent = GType . Object <$> jsg "OfflineAudioCompletionEvent"
newtype OfflineAudioContext = OfflineAudioContext { unOfflineAudioContext :: JSVal }
instance PToJSVal OfflineAudioContext where
pToJSVal = unOfflineAudioContext
{-# INLINE pToJSVal #-}
instance PFromJSVal OfflineAudioContext where
pFromJSVal = OfflineAudioContext
{-# INLINE pFromJSVal #-}
instance ToJSVal OfflineAudioContext where
toJSVal = return . unOfflineAudioContext
{-# INLINE toJSVal #-}
instance FromJSVal OfflineAudioContext where
fromJSVal v = fmap OfflineAudioContext <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OfflineAudioContext
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OfflineAudioContext where
makeObject = makeObject . unOfflineAudioContext
instance IsAudioContext OfflineAudioContext
instance IsEventTarget OfflineAudioContext
instance IsGObject OfflineAudioContext where
typeGType _ = gTypeOfflineAudioContext
{-# INLINE typeGType #-}
noOfflineAudioContext :: Maybe OfflineAudioContext
noOfflineAudioContext = Nothing
{-# INLINE noOfflineAudioContext #-}
gTypeOfflineAudioContext :: JSM GType
gTypeOfflineAudioContext = GType . Object <$> jsg "OfflineAudioContext"
newtype OscillatorNode = OscillatorNode { unOscillatorNode :: JSVal }
instance PToJSVal OscillatorNode where
pToJSVal = unOscillatorNode
{-# INLINE pToJSVal #-}
instance PFromJSVal OscillatorNode where
pFromJSVal = OscillatorNode
{-# INLINE pFromJSVal #-}
instance ToJSVal OscillatorNode where
toJSVal = return . unOscillatorNode
{-# INLINE toJSVal #-}
instance FromJSVal OscillatorNode where
fromJSVal v = fmap OscillatorNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OscillatorNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OscillatorNode where
makeObject = makeObject . unOscillatorNode
instance IsAudioNode OscillatorNode
instance IsEventTarget OscillatorNode
instance IsGObject OscillatorNode where
typeGType _ = gTypeOscillatorNode
{-# INLINE typeGType #-}
noOscillatorNode :: Maybe OscillatorNode
noOscillatorNode = Nothing
{-# INLINE noOscillatorNode #-}
gTypeOscillatorNode :: JSM GType
gTypeOscillatorNode = GType . Object <$> jsg "OscillatorNode"
newtype OverconstrainedError = OverconstrainedError { unOverconstrainedError :: JSVal }
instance PToJSVal OverconstrainedError where
pToJSVal = unOverconstrainedError
{-# INLINE pToJSVal #-}
instance PFromJSVal OverconstrainedError where
pFromJSVal = OverconstrainedError
{-# INLINE pFromJSVal #-}
instance ToJSVal OverconstrainedError where
toJSVal = return . unOverconstrainedError
{-# INLINE toJSVal #-}
instance FromJSVal OverconstrainedError where
fromJSVal v = fmap OverconstrainedError <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OverconstrainedError
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OverconstrainedError where
makeObject = makeObject . unOverconstrainedError
instance IsGObject OverconstrainedError where
typeGType _ = gTypeOverconstrainedError
{-# INLINE typeGType #-}
noOverconstrainedError :: Maybe OverconstrainedError
noOverconstrainedError = Nothing
{-# INLINE noOverconstrainedError #-}
gTypeOverconstrainedError :: JSM GType
gTypeOverconstrainedError = GType . Object <$> jsg "OverconstrainedError"
newtype OverconstrainedErrorEvent = OverconstrainedErrorEvent { unOverconstrainedErrorEvent :: JSVal }
instance PToJSVal OverconstrainedErrorEvent where
pToJSVal = unOverconstrainedErrorEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal OverconstrainedErrorEvent where
pFromJSVal = OverconstrainedErrorEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal OverconstrainedErrorEvent where
toJSVal = return . unOverconstrainedErrorEvent
{-# INLINE toJSVal #-}
instance FromJSVal OverconstrainedErrorEvent where
fromJSVal v = fmap OverconstrainedErrorEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OverconstrainedErrorEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OverconstrainedErrorEvent where
makeObject = makeObject . unOverconstrainedErrorEvent
instance IsEvent OverconstrainedErrorEvent
instance IsGObject OverconstrainedErrorEvent where
typeGType _ = gTypeOverconstrainedErrorEvent
{-# INLINE typeGType #-}
noOverconstrainedErrorEvent :: Maybe OverconstrainedErrorEvent
noOverconstrainedErrorEvent = Nothing
{-# INLINE noOverconstrainedErrorEvent #-}
gTypeOverconstrainedErrorEvent :: JSM GType
gTypeOverconstrainedErrorEvent = GType . Object <$> jsg "OverconstrainedErrorEvent"
newtype OverconstrainedErrorEventInit = OverconstrainedErrorEventInit { unOverconstrainedErrorEventInit :: JSVal }
instance PToJSVal OverconstrainedErrorEventInit where
pToJSVal = unOverconstrainedErrorEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal OverconstrainedErrorEventInit where
pFromJSVal = OverconstrainedErrorEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal OverconstrainedErrorEventInit where
toJSVal = return . unOverconstrainedErrorEventInit
{-# INLINE toJSVal #-}
instance FromJSVal OverconstrainedErrorEventInit where
fromJSVal v = fmap OverconstrainedErrorEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OverconstrainedErrorEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OverconstrainedErrorEventInit where
makeObject = makeObject . unOverconstrainedErrorEventInit
instance IsEventInit OverconstrainedErrorEventInit
instance IsGObject OverconstrainedErrorEventInit where
typeGType _ = gTypeOverconstrainedErrorEventInit
{-# INLINE typeGType #-}
noOverconstrainedErrorEventInit :: Maybe OverconstrainedErrorEventInit
noOverconstrainedErrorEventInit = Nothing
{-# INLINE noOverconstrainedErrorEventInit #-}
gTypeOverconstrainedErrorEventInit :: JSM GType
gTypeOverconstrainedErrorEventInit = GType . Object <$> jsg "OverconstrainedErrorEventInit"
newtype OverflowEvent = OverflowEvent { unOverflowEvent :: JSVal }
instance PToJSVal OverflowEvent where
pToJSVal = unOverflowEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal OverflowEvent where
pFromJSVal = OverflowEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal OverflowEvent where
toJSVal = return . unOverflowEvent
{-# INLINE toJSVal #-}
instance FromJSVal OverflowEvent where
fromJSVal v = fmap OverflowEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OverflowEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OverflowEvent where
makeObject = makeObject . unOverflowEvent
instance IsEvent OverflowEvent
instance IsGObject OverflowEvent where
typeGType _ = gTypeOverflowEvent
{-# INLINE typeGType #-}
noOverflowEvent :: Maybe OverflowEvent
noOverflowEvent = Nothing
{-# INLINE noOverflowEvent #-}
gTypeOverflowEvent :: JSM GType
gTypeOverflowEvent = GType . Object <$> jsg "OverflowEvent"
newtype OverflowEventInit = OverflowEventInit { unOverflowEventInit :: JSVal }
instance PToJSVal OverflowEventInit where
pToJSVal = unOverflowEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal OverflowEventInit where
pFromJSVal = OverflowEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal OverflowEventInit where
toJSVal = return . unOverflowEventInit
{-# INLINE toJSVal #-}
instance FromJSVal OverflowEventInit where
fromJSVal v = fmap OverflowEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . OverflowEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject OverflowEventInit where
makeObject = makeObject . unOverflowEventInit
instance IsEventInit OverflowEventInit
instance IsGObject OverflowEventInit where
typeGType _ = gTypeOverflowEventInit
{-# INLINE typeGType #-}
noOverflowEventInit :: Maybe OverflowEventInit
noOverflowEventInit = Nothing
{-# INLINE noOverflowEventInit #-}
gTypeOverflowEventInit :: JSM GType
gTypeOverflowEventInit = GType . Object <$> jsg "OverflowEventInit"
newtype PageTransitionEvent = PageTransitionEvent { unPageTransitionEvent :: JSVal }
instance PToJSVal PageTransitionEvent where
pToJSVal = unPageTransitionEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal PageTransitionEvent where
pFromJSVal = PageTransitionEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal PageTransitionEvent where
toJSVal = return . unPageTransitionEvent
{-# INLINE toJSVal #-}
instance FromJSVal PageTransitionEvent where
fromJSVal v = fmap PageTransitionEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PageTransitionEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PageTransitionEvent where
makeObject = makeObject . unPageTransitionEvent
instance IsEvent PageTransitionEvent
instance IsGObject PageTransitionEvent where
typeGType _ = gTypePageTransitionEvent
{-# INLINE typeGType #-}
noPageTransitionEvent :: Maybe PageTransitionEvent
noPageTransitionEvent = Nothing
{-# INLINE noPageTransitionEvent #-}
gTypePageTransitionEvent :: JSM GType
gTypePageTransitionEvent = GType . Object <$> jsg "PageTransitionEvent"
newtype PageTransitionEventInit = PageTransitionEventInit { unPageTransitionEventInit :: JSVal }
instance PToJSVal PageTransitionEventInit where
pToJSVal = unPageTransitionEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal PageTransitionEventInit where
pFromJSVal = PageTransitionEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal PageTransitionEventInit where
toJSVal = return . unPageTransitionEventInit
{-# INLINE toJSVal #-}
instance FromJSVal PageTransitionEventInit where
fromJSVal v = fmap PageTransitionEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PageTransitionEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PageTransitionEventInit where
makeObject = makeObject . unPageTransitionEventInit
instance IsEventInit PageTransitionEventInit
instance IsGObject PageTransitionEventInit where
typeGType _ = gTypePageTransitionEventInit
{-# INLINE typeGType #-}
noPageTransitionEventInit :: Maybe PageTransitionEventInit
noPageTransitionEventInit = Nothing
{-# INLINE noPageTransitionEventInit #-}
gTypePageTransitionEventInit :: JSM GType
gTypePageTransitionEventInit = GType . Object <$> jsg "PageTransitionEventInit"
newtype PannerNode = PannerNode { unPannerNode :: JSVal }
instance PToJSVal PannerNode where
pToJSVal = unPannerNode
{-# INLINE pToJSVal #-}
instance PFromJSVal PannerNode where
pFromJSVal = PannerNode
{-# INLINE pFromJSVal #-}
instance ToJSVal PannerNode where
toJSVal = return . unPannerNode
{-# INLINE toJSVal #-}
instance FromJSVal PannerNode where
fromJSVal v = fmap PannerNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PannerNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PannerNode where
makeObject = makeObject . unPannerNode
instance IsAudioNode PannerNode
instance IsEventTarget PannerNode
instance IsGObject PannerNode where
typeGType _ = gTypePannerNode
{-# INLINE typeGType #-}
noPannerNode :: Maybe PannerNode
noPannerNode = Nothing
{-# INLINE noPannerNode #-}
gTypePannerNode :: JSM GType
gTypePannerNode = GType . Object <$> jsg "webkitAudioPannerNode"
newtype ParentNode = ParentNode { unParentNode :: JSVal }
instance PToJSVal ParentNode where
pToJSVal = unParentNode
{-# INLINE pToJSVal #-}
instance PFromJSVal ParentNode where
pFromJSVal = ParentNode
{-# INLINE pFromJSVal #-}
instance ToJSVal ParentNode where
toJSVal = return . unParentNode
{-# INLINE toJSVal #-}
instance FromJSVal ParentNode where
fromJSVal v = fmap ParentNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ParentNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ParentNode where
makeObject = makeObject . unParentNode
class (IsGObject o) => IsParentNode o
toParentNode :: IsParentNode o => o -> ParentNode
toParentNode = ParentNode . coerce
instance IsParentNode ParentNode
instance IsGObject ParentNode where
typeGType _ = gTypeParentNode
{-# INLINE typeGType #-}
noParentNode :: Maybe ParentNode
noParentNode = Nothing
{-# INLINE noParentNode #-}
gTypeParentNode :: JSM GType
gTypeParentNode = GType . Object <$> jsg "ParentNode"
newtype PasswordCredential = PasswordCredential { unPasswordCredential :: JSVal }
instance PToJSVal PasswordCredential where
pToJSVal = unPasswordCredential
{-# INLINE pToJSVal #-}
instance PFromJSVal PasswordCredential where
pFromJSVal = PasswordCredential
{-# INLINE pFromJSVal #-}
instance ToJSVal PasswordCredential where
toJSVal = return . unPasswordCredential
{-# INLINE toJSVal #-}
instance FromJSVal PasswordCredential where
fromJSVal v = fmap PasswordCredential <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PasswordCredential
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PasswordCredential where
makeObject = makeObject . unPasswordCredential
instance IsSiteBoundCredential PasswordCredential
instance IsBasicCredential PasswordCredential
instance IsGObject PasswordCredential where
typeGType _ = gTypePasswordCredential
{-# INLINE typeGType #-}
noPasswordCredential :: Maybe PasswordCredential
noPasswordCredential = Nothing
{-# INLINE noPasswordCredential #-}
gTypePasswordCredential :: JSM GType
gTypePasswordCredential = GType . Object <$> jsg "PasswordCredential"
newtype PasswordCredentialData = PasswordCredentialData { unPasswordCredentialData :: JSVal }
instance PToJSVal PasswordCredentialData where
pToJSVal = unPasswordCredentialData
{-# INLINE pToJSVal #-}
instance PFromJSVal PasswordCredentialData where
pFromJSVal = PasswordCredentialData
{-# INLINE pFromJSVal #-}
instance ToJSVal PasswordCredentialData where
toJSVal = return . unPasswordCredentialData
{-# INLINE toJSVal #-}
instance FromJSVal PasswordCredentialData where
fromJSVal v = fmap PasswordCredentialData <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PasswordCredentialData
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PasswordCredentialData where
makeObject = makeObject . unPasswordCredentialData
instance IsSiteBoundCredentialData PasswordCredentialData
instance IsCredentialData PasswordCredentialData
instance IsGObject PasswordCredentialData where
typeGType _ = gTypePasswordCredentialData
{-# INLINE typeGType #-}
noPasswordCredentialData :: Maybe PasswordCredentialData
noPasswordCredentialData = Nothing
{-# INLINE noPasswordCredentialData #-}
gTypePasswordCredentialData :: JSM GType
gTypePasswordCredentialData = GType . Object <$> jsg "PasswordCredentialData"
newtype Path2D = Path2D { unPath2D :: JSVal }
instance PToJSVal Path2D where
pToJSVal = unPath2D
{-# INLINE pToJSVal #-}
instance PFromJSVal Path2D where
pFromJSVal = Path2D
{-# INLINE pFromJSVal #-}
instance ToJSVal Path2D where
toJSVal = return . unPath2D
{-# INLINE toJSVal #-}
instance FromJSVal Path2D where
fromJSVal v = fmap Path2D <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Path2D
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Path2D where
makeObject = makeObject . unPath2D
instance IsCanvasPath Path2D
instance IsGObject Path2D where
typeGType _ = gTypePath2D
{-# INLINE typeGType #-}
noPath2D :: Maybe Path2D
noPath2D = Nothing
{-# INLINE noPath2D #-}
gTypePath2D :: JSM GType
gTypePath2D = GType . Object <$> jsg "Path2D"
newtype Pbkdf2Params = Pbkdf2Params { unPbkdf2Params :: JSVal }
instance PToJSVal Pbkdf2Params where
pToJSVal = unPbkdf2Params
{-# INLINE pToJSVal #-}
instance PFromJSVal Pbkdf2Params where
pFromJSVal = Pbkdf2Params
{-# INLINE pFromJSVal #-}
instance ToJSVal Pbkdf2Params where
toJSVal = return . unPbkdf2Params
{-# INLINE toJSVal #-}
instance FromJSVal Pbkdf2Params where
fromJSVal v = fmap Pbkdf2Params <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Pbkdf2Params
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Pbkdf2Params where
makeObject = makeObject . unPbkdf2Params
instance IsCryptoAlgorithmParameters Pbkdf2Params
instance IsGObject Pbkdf2Params where
typeGType _ = gTypePbkdf2Params
{-# INLINE typeGType #-}
noPbkdf2Params :: Maybe Pbkdf2Params
noPbkdf2Params = Nothing
{-# INLINE noPbkdf2Params #-}
gTypePbkdf2Params :: JSM GType
gTypePbkdf2Params = GType . Object <$> jsg "Pbkdf2Params"
newtype Performance = Performance { unPerformance :: JSVal }
instance PToJSVal Performance where
pToJSVal = unPerformance
{-# INLINE pToJSVal #-}
instance PFromJSVal Performance where
pFromJSVal = Performance
{-# INLINE pFromJSVal #-}
instance ToJSVal Performance where
toJSVal = return . unPerformance
{-# INLINE toJSVal #-}
instance FromJSVal Performance where
fromJSVal v = fmap Performance <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Performance
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Performance where
makeObject = makeObject . unPerformance
instance IsEventTarget Performance
instance IsGObject Performance where
typeGType _ = gTypePerformance
{-# INLINE typeGType #-}
noPerformance :: Maybe Performance
noPerformance = Nothing
{-# INLINE noPerformance #-}
gTypePerformance :: JSM GType
gTypePerformance = GType . Object <$> jsg "Performance"
newtype PerformanceEntry = PerformanceEntry { unPerformanceEntry :: JSVal }
instance PToJSVal PerformanceEntry where
pToJSVal = unPerformanceEntry
{-# INLINE pToJSVal #-}
instance PFromJSVal PerformanceEntry where
pFromJSVal = PerformanceEntry
{-# INLINE pFromJSVal #-}
instance ToJSVal PerformanceEntry where
toJSVal = return . unPerformanceEntry
{-# INLINE toJSVal #-}
instance FromJSVal PerformanceEntry where
fromJSVal v = fmap PerformanceEntry <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PerformanceEntry
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PerformanceEntry where
makeObject = makeObject . unPerformanceEntry
class (IsGObject o) => IsPerformanceEntry o
toPerformanceEntry :: IsPerformanceEntry o => o -> PerformanceEntry
toPerformanceEntry = PerformanceEntry . coerce
instance IsPerformanceEntry PerformanceEntry
instance IsGObject PerformanceEntry where
typeGType _ = gTypePerformanceEntry
{-# INLINE typeGType #-}
noPerformanceEntry :: Maybe PerformanceEntry
noPerformanceEntry = Nothing
{-# INLINE noPerformanceEntry #-}
gTypePerformanceEntry :: JSM GType
gTypePerformanceEntry = GType . Object <$> jsg "PerformanceEntry"
newtype PerformanceMark = PerformanceMark { unPerformanceMark :: JSVal }
instance PToJSVal PerformanceMark where
pToJSVal = unPerformanceMark
{-# INLINE pToJSVal #-}
instance PFromJSVal PerformanceMark where
pFromJSVal = PerformanceMark
{-# INLINE pFromJSVal #-}
instance ToJSVal PerformanceMark where
toJSVal = return . unPerformanceMark
{-# INLINE toJSVal #-}
instance FromJSVal PerformanceMark where
fromJSVal v = fmap PerformanceMark <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PerformanceMark
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PerformanceMark where
makeObject = makeObject . unPerformanceMark
instance IsPerformanceEntry PerformanceMark
instance IsGObject PerformanceMark where
typeGType _ = gTypePerformanceMark
{-# INLINE typeGType #-}
noPerformanceMark :: Maybe PerformanceMark
noPerformanceMark = Nothing
{-# INLINE noPerformanceMark #-}
gTypePerformanceMark :: JSM GType
gTypePerformanceMark = GType . Object <$> jsg "PerformanceMark"
newtype PerformanceMeasure = PerformanceMeasure { unPerformanceMeasure :: JSVal }
instance PToJSVal PerformanceMeasure where
pToJSVal = unPerformanceMeasure
{-# INLINE pToJSVal #-}
instance PFromJSVal PerformanceMeasure where
pFromJSVal = PerformanceMeasure
{-# INLINE pFromJSVal #-}
instance ToJSVal PerformanceMeasure where
toJSVal = return . unPerformanceMeasure
{-# INLINE toJSVal #-}
instance FromJSVal PerformanceMeasure where
fromJSVal v = fmap PerformanceMeasure <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PerformanceMeasure
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PerformanceMeasure where
makeObject = makeObject . unPerformanceMeasure
instance IsPerformanceEntry PerformanceMeasure
instance IsGObject PerformanceMeasure where
typeGType _ = gTypePerformanceMeasure
{-# INLINE typeGType #-}
noPerformanceMeasure :: Maybe PerformanceMeasure
noPerformanceMeasure = Nothing
{-# INLINE noPerformanceMeasure #-}
gTypePerformanceMeasure :: JSM GType
gTypePerformanceMeasure = GType . Object <$> jsg "PerformanceMeasure"
newtype PerformanceNavigation = PerformanceNavigation { unPerformanceNavigation :: JSVal }
instance PToJSVal PerformanceNavigation where
pToJSVal = unPerformanceNavigation
{-# INLINE pToJSVal #-}
instance PFromJSVal PerformanceNavigation where
pFromJSVal = PerformanceNavigation
{-# INLINE pFromJSVal #-}
instance ToJSVal PerformanceNavigation where
toJSVal = return . unPerformanceNavigation
{-# INLINE toJSVal #-}
instance FromJSVal PerformanceNavigation where
fromJSVal v = fmap PerformanceNavigation <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PerformanceNavigation
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PerformanceNavigation where
makeObject = makeObject . unPerformanceNavigation
instance IsGObject PerformanceNavigation where
typeGType _ = gTypePerformanceNavigation
{-# INLINE typeGType #-}
noPerformanceNavigation :: Maybe PerformanceNavigation
noPerformanceNavigation = Nothing
{-# INLINE noPerformanceNavigation #-}
gTypePerformanceNavigation :: JSM GType
gTypePerformanceNavigation = GType . Object <$> jsg "PerformanceNavigation"
newtype PerformanceObserver = PerformanceObserver { unPerformanceObserver :: JSVal }
instance PToJSVal PerformanceObserver where
pToJSVal = unPerformanceObserver
{-# INLINE pToJSVal #-}
instance PFromJSVal PerformanceObserver where
pFromJSVal = PerformanceObserver
{-# INLINE pFromJSVal #-}
instance ToJSVal PerformanceObserver where
toJSVal = return . unPerformanceObserver
{-# INLINE toJSVal #-}
instance FromJSVal PerformanceObserver where
fromJSVal v = fmap PerformanceObserver <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PerformanceObserver
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PerformanceObserver where
makeObject = makeObject . unPerformanceObserver
instance IsGObject PerformanceObserver where
typeGType _ = gTypePerformanceObserver
{-# INLINE typeGType #-}
noPerformanceObserver :: Maybe PerformanceObserver
noPerformanceObserver = Nothing
{-# INLINE noPerformanceObserver #-}
gTypePerformanceObserver :: JSM GType
gTypePerformanceObserver = GType . Object <$> jsg "PerformanceObserver"
newtype PerformanceObserverEntryList = PerformanceObserverEntryList { unPerformanceObserverEntryList :: JSVal }
instance PToJSVal PerformanceObserverEntryList where
pToJSVal = unPerformanceObserverEntryList
{-# INLINE pToJSVal #-}
instance PFromJSVal PerformanceObserverEntryList where
pFromJSVal = PerformanceObserverEntryList
{-# INLINE pFromJSVal #-}
instance ToJSVal PerformanceObserverEntryList where
toJSVal = return . unPerformanceObserverEntryList
{-# INLINE toJSVal #-}
instance FromJSVal PerformanceObserverEntryList where
fromJSVal v = fmap PerformanceObserverEntryList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PerformanceObserverEntryList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PerformanceObserverEntryList where
makeObject = makeObject . unPerformanceObserverEntryList
instance IsGObject PerformanceObserverEntryList where
typeGType _ = gTypePerformanceObserverEntryList
{-# INLINE typeGType #-}
noPerformanceObserverEntryList :: Maybe PerformanceObserverEntryList
noPerformanceObserverEntryList = Nothing
{-# INLINE noPerformanceObserverEntryList #-}
gTypePerformanceObserverEntryList :: JSM GType
gTypePerformanceObserverEntryList = GType . Object <$> jsg "PerformanceObserverEntryList"
newtype PerformanceObserverInit = PerformanceObserverInit { unPerformanceObserverInit :: JSVal }
instance PToJSVal PerformanceObserverInit where
pToJSVal = unPerformanceObserverInit
{-# INLINE pToJSVal #-}
instance PFromJSVal PerformanceObserverInit where
pFromJSVal = PerformanceObserverInit
{-# INLINE pFromJSVal #-}
instance ToJSVal PerformanceObserverInit where
toJSVal = return . unPerformanceObserverInit
{-# INLINE toJSVal #-}
instance FromJSVal PerformanceObserverInit where
fromJSVal v = fmap PerformanceObserverInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PerformanceObserverInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PerformanceObserverInit where
makeObject = makeObject . unPerformanceObserverInit
instance IsGObject PerformanceObserverInit where
typeGType _ = gTypePerformanceObserverInit
{-# INLINE typeGType #-}
noPerformanceObserverInit :: Maybe PerformanceObserverInit
noPerformanceObserverInit = Nothing
{-# INLINE noPerformanceObserverInit #-}
gTypePerformanceObserverInit :: JSM GType
gTypePerformanceObserverInit = GType . Object <$> jsg "PerformanceObserverInit"
newtype PerformanceResourceTiming = PerformanceResourceTiming { unPerformanceResourceTiming :: JSVal }
instance PToJSVal PerformanceResourceTiming where
pToJSVal = unPerformanceResourceTiming
{-# INLINE pToJSVal #-}
instance PFromJSVal PerformanceResourceTiming where
pFromJSVal = PerformanceResourceTiming
{-# INLINE pFromJSVal #-}
instance ToJSVal PerformanceResourceTiming where
toJSVal = return . unPerformanceResourceTiming
{-# INLINE toJSVal #-}
instance FromJSVal PerformanceResourceTiming where
fromJSVal v = fmap PerformanceResourceTiming <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PerformanceResourceTiming
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PerformanceResourceTiming where
makeObject = makeObject . unPerformanceResourceTiming
instance IsPerformanceEntry PerformanceResourceTiming
instance IsGObject PerformanceResourceTiming where
typeGType _ = gTypePerformanceResourceTiming
{-# INLINE typeGType #-}
noPerformanceResourceTiming :: Maybe PerformanceResourceTiming
noPerformanceResourceTiming = Nothing
{-# INLINE noPerformanceResourceTiming #-}
gTypePerformanceResourceTiming :: JSM GType
gTypePerformanceResourceTiming = GType . Object <$> jsg "PerformanceResourceTiming"
newtype PerformanceTiming = PerformanceTiming { unPerformanceTiming :: JSVal }
instance PToJSVal PerformanceTiming where
pToJSVal = unPerformanceTiming
{-# INLINE pToJSVal #-}
instance PFromJSVal PerformanceTiming where
pFromJSVal = PerformanceTiming
{-# INLINE pFromJSVal #-}
instance ToJSVal PerformanceTiming where
toJSVal = return . unPerformanceTiming
{-# INLINE toJSVal #-}
instance FromJSVal PerformanceTiming where
fromJSVal v = fmap PerformanceTiming <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PerformanceTiming
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PerformanceTiming where
makeObject = makeObject . unPerformanceTiming
instance IsGObject PerformanceTiming where
typeGType _ = gTypePerformanceTiming
{-# INLINE typeGType #-}
noPerformanceTiming :: Maybe PerformanceTiming
noPerformanceTiming = Nothing
{-# INLINE noPerformanceTiming #-}
gTypePerformanceTiming :: JSM GType
gTypePerformanceTiming = GType . Object <$> jsg "PerformanceTiming"
newtype PeriodicWave = PeriodicWave { unPeriodicWave :: JSVal }
instance PToJSVal PeriodicWave where
pToJSVal = unPeriodicWave
{-# INLINE pToJSVal #-}
instance PFromJSVal PeriodicWave where
pFromJSVal = PeriodicWave
{-# INLINE pFromJSVal #-}
instance ToJSVal PeriodicWave where
toJSVal = return . unPeriodicWave
{-# INLINE toJSVal #-}
instance FromJSVal PeriodicWave where
fromJSVal v = fmap PeriodicWave <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PeriodicWave
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PeriodicWave where
makeObject = makeObject . unPeriodicWave
instance IsGObject PeriodicWave where
typeGType _ = gTypePeriodicWave
{-# INLINE typeGType #-}
noPeriodicWave :: Maybe PeriodicWave
noPeriodicWave = Nothing
{-# INLINE noPeriodicWave #-}
gTypePeriodicWave :: JSM GType
gTypePeriodicWave = GType . Object <$> jsg "PeriodicWave"
newtype Plugin = Plugin { unPlugin :: JSVal }
instance PToJSVal Plugin where
pToJSVal = unPlugin
{-# INLINE pToJSVal #-}
instance PFromJSVal Plugin where
pFromJSVal = Plugin
{-# INLINE pFromJSVal #-}
instance ToJSVal Plugin where
toJSVal = return . unPlugin
{-# INLINE toJSVal #-}
instance FromJSVal Plugin where
fromJSVal v = fmap Plugin <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Plugin
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Plugin where
makeObject = makeObject . unPlugin
instance IsGObject Plugin where
typeGType _ = gTypePlugin
{-# INLINE typeGType #-}
noPlugin :: Maybe Plugin
noPlugin = Nothing
{-# INLINE noPlugin #-}
gTypePlugin :: JSM GType
gTypePlugin = GType . Object <$> jsg "Plugin"
newtype PluginArray = PluginArray { unPluginArray :: JSVal }
instance PToJSVal PluginArray where
pToJSVal = unPluginArray
{-# INLINE pToJSVal #-}
instance PFromJSVal PluginArray where
pFromJSVal = PluginArray
{-# INLINE pFromJSVal #-}
instance ToJSVal PluginArray where
toJSVal = return . unPluginArray
{-# INLINE toJSVal #-}
instance FromJSVal PluginArray where
fromJSVal v = fmap PluginArray <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PluginArray
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PluginArray where
makeObject = makeObject . unPluginArray
instance IsGObject PluginArray where
typeGType _ = gTypePluginArray
{-# INLINE typeGType #-}
noPluginArray :: Maybe PluginArray
noPluginArray = Nothing
{-# INLINE noPluginArray #-}
gTypePluginArray :: JSM GType
gTypePluginArray = GType . Object <$> jsg "PluginArray"
newtype PopStateEvent = PopStateEvent { unPopStateEvent :: JSVal }
instance PToJSVal PopStateEvent where
pToJSVal = unPopStateEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal PopStateEvent where
pFromJSVal = PopStateEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal PopStateEvent where
toJSVal = return . unPopStateEvent
{-# INLINE toJSVal #-}
instance FromJSVal PopStateEvent where
fromJSVal v = fmap PopStateEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PopStateEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PopStateEvent where
makeObject = makeObject . unPopStateEvent
instance IsEvent PopStateEvent
instance IsGObject PopStateEvent where
typeGType _ = gTypePopStateEvent
{-# INLINE typeGType #-}
noPopStateEvent :: Maybe PopStateEvent
noPopStateEvent = Nothing
{-# INLINE noPopStateEvent #-}
gTypePopStateEvent :: JSM GType
gTypePopStateEvent = GType . Object <$> jsg "PopStateEvent"
newtype PopStateEventInit = PopStateEventInit { unPopStateEventInit :: JSVal }
instance PToJSVal PopStateEventInit where
pToJSVal = unPopStateEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal PopStateEventInit where
pFromJSVal = PopStateEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal PopStateEventInit where
toJSVal = return . unPopStateEventInit
{-# INLINE toJSVal #-}
instance FromJSVal PopStateEventInit where
fromJSVal v = fmap PopStateEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PopStateEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PopStateEventInit where
makeObject = makeObject . unPopStateEventInit
instance IsEventInit PopStateEventInit
instance IsGObject PopStateEventInit where
typeGType _ = gTypePopStateEventInit
{-# INLINE typeGType #-}
noPopStateEventInit :: Maybe PopStateEventInit
noPopStateEventInit = Nothing
{-# INLINE noPopStateEventInit #-}
gTypePopStateEventInit :: JSM GType
gTypePopStateEventInit = GType . Object <$> jsg "PopStateEventInit"
newtype PositionError = PositionError { unPositionError :: JSVal }
instance PToJSVal PositionError where
pToJSVal = unPositionError
{-# INLINE pToJSVal #-}
instance PFromJSVal PositionError where
pFromJSVal = PositionError
{-# INLINE pFromJSVal #-}
instance ToJSVal PositionError where
toJSVal = return . unPositionError
{-# INLINE toJSVal #-}
instance FromJSVal PositionError where
fromJSVal v = fmap PositionError <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PositionError
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PositionError where
makeObject = makeObject . unPositionError
instance IsGObject PositionError where
typeGType _ = gTypePositionError
{-# INLINE typeGType #-}
noPositionError :: Maybe PositionError
noPositionError = Nothing
{-# INLINE noPositionError #-}
gTypePositionError :: JSM GType
gTypePositionError = GType . Object <$> jsg "PositionError"
newtype PositionOptions = PositionOptions { unPositionOptions :: JSVal }
instance PToJSVal PositionOptions where
pToJSVal = unPositionOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal PositionOptions where
pFromJSVal = PositionOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal PositionOptions where
toJSVal = return . unPositionOptions
{-# INLINE toJSVal #-}
instance FromJSVal PositionOptions where
fromJSVal v = fmap PositionOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PositionOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PositionOptions where
makeObject = makeObject . unPositionOptions
instance IsGObject PositionOptions where
typeGType _ = gTypePositionOptions
{-# INLINE typeGType #-}
noPositionOptions :: Maybe PositionOptions
noPositionOptions = Nothing
{-# INLINE noPositionOptions #-}
gTypePositionOptions :: JSM GType
gTypePositionOptions = GType . Object <$> jsg "PositionOptions"
newtype ProcessingInstruction = ProcessingInstruction { unProcessingInstruction :: JSVal }
instance PToJSVal ProcessingInstruction where
pToJSVal = unProcessingInstruction
{-# INLINE pToJSVal #-}
instance PFromJSVal ProcessingInstruction where
pFromJSVal = ProcessingInstruction
{-# INLINE pFromJSVal #-}
instance ToJSVal ProcessingInstruction where
toJSVal = return . unProcessingInstruction
{-# INLINE toJSVal #-}
instance FromJSVal ProcessingInstruction where
fromJSVal v = fmap ProcessingInstruction <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ProcessingInstruction
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ProcessingInstruction where
makeObject = makeObject . unProcessingInstruction
instance IsCharacterData ProcessingInstruction
instance IsNode ProcessingInstruction
instance IsEventTarget ProcessingInstruction
instance IsNonDocumentTypeChildNode ProcessingInstruction
instance IsChildNode ProcessingInstruction
instance IsGObject ProcessingInstruction where
typeGType _ = gTypeProcessingInstruction
{-# INLINE typeGType #-}
noProcessingInstruction :: Maybe ProcessingInstruction
noProcessingInstruction = Nothing
{-# INLINE noProcessingInstruction #-}
gTypeProcessingInstruction :: JSM GType
gTypeProcessingInstruction = GType . Object <$> jsg "ProcessingInstruction"
newtype ProgressEvent = ProgressEvent { unProgressEvent :: JSVal }
instance PToJSVal ProgressEvent where
pToJSVal = unProgressEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal ProgressEvent where
pFromJSVal = ProgressEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal ProgressEvent where
toJSVal = return . unProgressEvent
{-# INLINE toJSVal #-}
instance FromJSVal ProgressEvent where
fromJSVal v = fmap ProgressEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ProgressEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ProgressEvent where
makeObject = makeObject . unProgressEvent
class (IsEvent o, IsGObject o) => IsProgressEvent o
toProgressEvent :: IsProgressEvent o => o -> ProgressEvent
toProgressEvent = ProgressEvent . coerce
instance IsProgressEvent ProgressEvent
instance IsEvent ProgressEvent
instance IsGObject ProgressEvent where
typeGType _ = gTypeProgressEvent
{-# INLINE typeGType #-}
noProgressEvent :: Maybe ProgressEvent
noProgressEvent = Nothing
{-# INLINE noProgressEvent #-}
gTypeProgressEvent :: JSM GType
gTypeProgressEvent = GType . Object <$> jsg "ProgressEvent"
newtype ProgressEventInit = ProgressEventInit { unProgressEventInit :: JSVal }
instance PToJSVal ProgressEventInit where
pToJSVal = unProgressEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal ProgressEventInit where
pFromJSVal = ProgressEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal ProgressEventInit where
toJSVal = return . unProgressEventInit
{-# INLINE toJSVal #-}
instance FromJSVal ProgressEventInit where
fromJSVal v = fmap ProgressEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ProgressEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ProgressEventInit where
makeObject = makeObject . unProgressEventInit
instance IsEventInit ProgressEventInit
instance IsGObject ProgressEventInit where
typeGType _ = gTypeProgressEventInit
{-# INLINE typeGType #-}
noProgressEventInit :: Maybe ProgressEventInit
noProgressEventInit = Nothing
{-# INLINE noProgressEventInit #-}
gTypeProgressEventInit :: JSM GType
gTypeProgressEventInit = GType . Object <$> jsg "ProgressEventInit"
newtype PromiseRejectionEvent = PromiseRejectionEvent { unPromiseRejectionEvent :: JSVal }
instance PToJSVal PromiseRejectionEvent where
pToJSVal = unPromiseRejectionEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal PromiseRejectionEvent where
pFromJSVal = PromiseRejectionEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal PromiseRejectionEvent where
toJSVal = return . unPromiseRejectionEvent
{-# INLINE toJSVal #-}
instance FromJSVal PromiseRejectionEvent where
fromJSVal v = fmap PromiseRejectionEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PromiseRejectionEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PromiseRejectionEvent where
makeObject = makeObject . unPromiseRejectionEvent
instance IsEvent PromiseRejectionEvent
instance IsGObject PromiseRejectionEvent where
typeGType _ = gTypePromiseRejectionEvent
{-# INLINE typeGType #-}
noPromiseRejectionEvent :: Maybe PromiseRejectionEvent
noPromiseRejectionEvent = Nothing
{-# INLINE noPromiseRejectionEvent #-}
gTypePromiseRejectionEvent :: JSM GType
gTypePromiseRejectionEvent = GType . Object <$> jsg "PromiseRejectionEvent"
newtype PromiseRejectionEventInit = PromiseRejectionEventInit { unPromiseRejectionEventInit :: JSVal }
instance PToJSVal PromiseRejectionEventInit where
pToJSVal = unPromiseRejectionEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal PromiseRejectionEventInit where
pFromJSVal = PromiseRejectionEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal PromiseRejectionEventInit where
toJSVal = return . unPromiseRejectionEventInit
{-# INLINE toJSVal #-}
instance FromJSVal PromiseRejectionEventInit where
fromJSVal v = fmap PromiseRejectionEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . PromiseRejectionEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject PromiseRejectionEventInit where
makeObject = makeObject . unPromiseRejectionEventInit
instance IsEventInit PromiseRejectionEventInit
instance IsGObject PromiseRejectionEventInit where
typeGType _ = gTypePromiseRejectionEventInit
{-# INLINE typeGType #-}
noPromiseRejectionEventInit :: Maybe PromiseRejectionEventInit
noPromiseRejectionEventInit = Nothing
{-# INLINE noPromiseRejectionEventInit #-}
gTypePromiseRejectionEventInit :: JSM GType
gTypePromiseRejectionEventInit = GType . Object <$> jsg "PromiseRejectionEventInit"
newtype QuickTimePluginReplacement = QuickTimePluginReplacement { unQuickTimePluginReplacement :: JSVal }
instance PToJSVal QuickTimePluginReplacement where
pToJSVal = unQuickTimePluginReplacement
{-# INLINE pToJSVal #-}
instance PFromJSVal QuickTimePluginReplacement where
pFromJSVal = QuickTimePluginReplacement
{-# INLINE pFromJSVal #-}
instance ToJSVal QuickTimePluginReplacement where
toJSVal = return . unQuickTimePluginReplacement
{-# INLINE toJSVal #-}
instance FromJSVal QuickTimePluginReplacement where
fromJSVal v = fmap QuickTimePluginReplacement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . QuickTimePluginReplacement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject QuickTimePluginReplacement where
makeObject = makeObject . unQuickTimePluginReplacement
instance IsGObject QuickTimePluginReplacement where
typeGType _ = gTypeQuickTimePluginReplacement
{-# INLINE typeGType #-}
noQuickTimePluginReplacement :: Maybe QuickTimePluginReplacement
noQuickTimePluginReplacement = Nothing
{-# INLINE noQuickTimePluginReplacement #-}
gTypeQuickTimePluginReplacement :: JSM GType
gTypeQuickTimePluginReplacement = GType . Object <$> jsg "QuickTimePluginReplacement"
newtype RGBColor = RGBColor { unRGBColor :: JSVal }
instance PToJSVal RGBColor where
pToJSVal = unRGBColor
{-# INLINE pToJSVal #-}
instance PFromJSVal RGBColor where
pFromJSVal = RGBColor
{-# INLINE pFromJSVal #-}
instance ToJSVal RGBColor where
toJSVal = return . unRGBColor
{-# INLINE toJSVal #-}
instance FromJSVal RGBColor where
fromJSVal v = fmap RGBColor <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RGBColor
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RGBColor where
makeObject = makeObject . unRGBColor
instance IsGObject RGBColor where
typeGType _ = gTypeRGBColor
{-# INLINE typeGType #-}
noRGBColor :: Maybe RGBColor
noRGBColor = Nothing
{-# INLINE noRGBColor #-}
gTypeRGBColor :: JSM GType
gTypeRGBColor = GType . Object <$> jsg "RGBColor"
newtype RTCAnswerOptions = RTCAnswerOptions { unRTCAnswerOptions :: JSVal }
instance PToJSVal RTCAnswerOptions where
pToJSVal = unRTCAnswerOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCAnswerOptions where
pFromJSVal = RTCAnswerOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCAnswerOptions where
toJSVal = return . unRTCAnswerOptions
{-# INLINE toJSVal #-}
instance FromJSVal RTCAnswerOptions where
fromJSVal v = fmap RTCAnswerOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCAnswerOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCAnswerOptions where
makeObject = makeObject . unRTCAnswerOptions
instance IsRTCOfferAnswerOptions RTCAnswerOptions
instance IsGObject RTCAnswerOptions where
typeGType _ = gTypeRTCAnswerOptions
{-# INLINE typeGType #-}
noRTCAnswerOptions :: Maybe RTCAnswerOptions
noRTCAnswerOptions = Nothing
{-# INLINE noRTCAnswerOptions #-}
gTypeRTCAnswerOptions :: JSM GType
gTypeRTCAnswerOptions = GType . Object <$> jsg "RTCAnswerOptions"
newtype RTCConfiguration = RTCConfiguration { unRTCConfiguration :: JSVal }
instance PToJSVal RTCConfiguration where
pToJSVal = unRTCConfiguration
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCConfiguration where
pFromJSVal = RTCConfiguration
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCConfiguration where
toJSVal = return . unRTCConfiguration
{-# INLINE toJSVal #-}
instance FromJSVal RTCConfiguration where
fromJSVal v = fmap RTCConfiguration <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCConfiguration
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCConfiguration where
makeObject = makeObject . unRTCConfiguration
instance IsGObject RTCConfiguration where
typeGType _ = gTypeRTCConfiguration
{-# INLINE typeGType #-}
noRTCConfiguration :: Maybe RTCConfiguration
noRTCConfiguration = Nothing
{-# INLINE noRTCConfiguration #-}
gTypeRTCConfiguration :: JSM GType
gTypeRTCConfiguration = GType . Object <$> jsg "RTCConfiguration"
newtype RTCDTMFSender = RTCDTMFSender { unRTCDTMFSender :: JSVal }
instance PToJSVal RTCDTMFSender where
pToJSVal = unRTCDTMFSender
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCDTMFSender where
pFromJSVal = RTCDTMFSender
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCDTMFSender where
toJSVal = return . unRTCDTMFSender
{-# INLINE toJSVal #-}
instance FromJSVal RTCDTMFSender where
fromJSVal v = fmap RTCDTMFSender <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCDTMFSender
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCDTMFSender where
makeObject = makeObject . unRTCDTMFSender
instance IsEventTarget RTCDTMFSender
instance IsGObject RTCDTMFSender where
typeGType _ = gTypeRTCDTMFSender
{-# INLINE typeGType #-}
noRTCDTMFSender :: Maybe RTCDTMFSender
noRTCDTMFSender = Nothing
{-# INLINE noRTCDTMFSender #-}
gTypeRTCDTMFSender :: JSM GType
gTypeRTCDTMFSender = GType . Object <$> jsg "RTCDTMFSender"
newtype RTCDTMFToneChangeEvent = RTCDTMFToneChangeEvent { unRTCDTMFToneChangeEvent :: JSVal }
instance PToJSVal RTCDTMFToneChangeEvent where
pToJSVal = unRTCDTMFToneChangeEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCDTMFToneChangeEvent where
pFromJSVal = RTCDTMFToneChangeEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCDTMFToneChangeEvent where
toJSVal = return . unRTCDTMFToneChangeEvent
{-# INLINE toJSVal #-}
instance FromJSVal RTCDTMFToneChangeEvent where
fromJSVal v = fmap RTCDTMFToneChangeEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCDTMFToneChangeEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCDTMFToneChangeEvent where
makeObject = makeObject . unRTCDTMFToneChangeEvent
instance IsEvent RTCDTMFToneChangeEvent
instance IsGObject RTCDTMFToneChangeEvent where
typeGType _ = gTypeRTCDTMFToneChangeEvent
{-# INLINE typeGType #-}
noRTCDTMFToneChangeEvent :: Maybe RTCDTMFToneChangeEvent
noRTCDTMFToneChangeEvent = Nothing
{-# INLINE noRTCDTMFToneChangeEvent #-}
gTypeRTCDTMFToneChangeEvent :: JSM GType
gTypeRTCDTMFToneChangeEvent = GType . Object <$> jsg "RTCDTMFToneChangeEvent"
newtype RTCDTMFToneChangeEventInit = RTCDTMFToneChangeEventInit { unRTCDTMFToneChangeEventInit :: JSVal }
instance PToJSVal RTCDTMFToneChangeEventInit where
pToJSVal = unRTCDTMFToneChangeEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCDTMFToneChangeEventInit where
pFromJSVal = RTCDTMFToneChangeEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCDTMFToneChangeEventInit where
toJSVal = return . unRTCDTMFToneChangeEventInit
{-# INLINE toJSVal #-}
instance FromJSVal RTCDTMFToneChangeEventInit where
fromJSVal v = fmap RTCDTMFToneChangeEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCDTMFToneChangeEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCDTMFToneChangeEventInit where
makeObject = makeObject . unRTCDTMFToneChangeEventInit
instance IsEventInit RTCDTMFToneChangeEventInit
instance IsGObject RTCDTMFToneChangeEventInit where
typeGType _ = gTypeRTCDTMFToneChangeEventInit
{-# INLINE typeGType #-}
noRTCDTMFToneChangeEventInit :: Maybe RTCDTMFToneChangeEventInit
noRTCDTMFToneChangeEventInit = Nothing
{-# INLINE noRTCDTMFToneChangeEventInit #-}
gTypeRTCDTMFToneChangeEventInit :: JSM GType
gTypeRTCDTMFToneChangeEventInit = GType . Object <$> jsg "RTCDTMFToneChangeEventInit"
newtype RTCDataChannel = RTCDataChannel { unRTCDataChannel :: JSVal }
instance PToJSVal RTCDataChannel where
pToJSVal = unRTCDataChannel
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCDataChannel where
pFromJSVal = RTCDataChannel
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCDataChannel where
toJSVal = return . unRTCDataChannel
{-# INLINE toJSVal #-}
instance FromJSVal RTCDataChannel where
fromJSVal v = fmap RTCDataChannel <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCDataChannel
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCDataChannel where
makeObject = makeObject . unRTCDataChannel
instance IsEventTarget RTCDataChannel
instance IsGObject RTCDataChannel where
typeGType _ = gTypeRTCDataChannel
{-# INLINE typeGType #-}
noRTCDataChannel :: Maybe RTCDataChannel
noRTCDataChannel = Nothing
{-# INLINE noRTCDataChannel #-}
gTypeRTCDataChannel :: JSM GType
gTypeRTCDataChannel = GType . Object <$> jsg "RTCDataChannel"
newtype RTCDataChannelEvent = RTCDataChannelEvent { unRTCDataChannelEvent :: JSVal }
instance PToJSVal RTCDataChannelEvent where
pToJSVal = unRTCDataChannelEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCDataChannelEvent where
pFromJSVal = RTCDataChannelEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCDataChannelEvent where
toJSVal = return . unRTCDataChannelEvent
{-# INLINE toJSVal #-}
instance FromJSVal RTCDataChannelEvent where
fromJSVal v = fmap RTCDataChannelEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCDataChannelEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCDataChannelEvent where
makeObject = makeObject . unRTCDataChannelEvent
instance IsEvent RTCDataChannelEvent
instance IsGObject RTCDataChannelEvent where
typeGType _ = gTypeRTCDataChannelEvent
{-# INLINE typeGType #-}
noRTCDataChannelEvent :: Maybe RTCDataChannelEvent
noRTCDataChannelEvent = Nothing
{-# INLINE noRTCDataChannelEvent #-}
gTypeRTCDataChannelEvent :: JSM GType
gTypeRTCDataChannelEvent = GType . Object <$> jsg "RTCDataChannelEvent"
newtype RTCDataChannelEventInit = RTCDataChannelEventInit { unRTCDataChannelEventInit :: JSVal }
instance PToJSVal RTCDataChannelEventInit where
pToJSVal = unRTCDataChannelEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCDataChannelEventInit where
pFromJSVal = RTCDataChannelEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCDataChannelEventInit where
toJSVal = return . unRTCDataChannelEventInit
{-# INLINE toJSVal #-}
instance FromJSVal RTCDataChannelEventInit where
fromJSVal v = fmap RTCDataChannelEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCDataChannelEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCDataChannelEventInit where
makeObject = makeObject . unRTCDataChannelEventInit
instance IsEventInit RTCDataChannelEventInit
instance IsGObject RTCDataChannelEventInit where
typeGType _ = gTypeRTCDataChannelEventInit
{-# INLINE typeGType #-}
noRTCDataChannelEventInit :: Maybe RTCDataChannelEventInit
noRTCDataChannelEventInit = Nothing
{-# INLINE noRTCDataChannelEventInit #-}
gTypeRTCDataChannelEventInit :: JSM GType
gTypeRTCDataChannelEventInit = GType . Object <$> jsg "RTCDataChannelEventInit"
newtype RTCDataChannelInit = RTCDataChannelInit { unRTCDataChannelInit :: JSVal }
instance PToJSVal RTCDataChannelInit where
pToJSVal = unRTCDataChannelInit
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCDataChannelInit where
pFromJSVal = RTCDataChannelInit
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCDataChannelInit where
toJSVal = return . unRTCDataChannelInit
{-# INLINE toJSVal #-}
instance FromJSVal RTCDataChannelInit where
fromJSVal v = fmap RTCDataChannelInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCDataChannelInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCDataChannelInit where
makeObject = makeObject . unRTCDataChannelInit
instance IsGObject RTCDataChannelInit where
typeGType _ = gTypeRTCDataChannelInit
{-# INLINE typeGType #-}
noRTCDataChannelInit :: Maybe RTCDataChannelInit
noRTCDataChannelInit = Nothing
{-# INLINE noRTCDataChannelInit #-}
gTypeRTCDataChannelInit :: JSM GType
gTypeRTCDataChannelInit = GType . Object <$> jsg "RTCDataChannelInit"
newtype RTCDataChannelStats = RTCDataChannelStats { unRTCDataChannelStats :: JSVal }
instance PToJSVal RTCDataChannelStats where
pToJSVal = unRTCDataChannelStats
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCDataChannelStats where
pFromJSVal = RTCDataChannelStats
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCDataChannelStats where
toJSVal = return . unRTCDataChannelStats
{-# INLINE toJSVal #-}
instance FromJSVal RTCDataChannelStats where
fromJSVal v = fmap RTCDataChannelStats <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCDataChannelStats
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCDataChannelStats where
makeObject = makeObject . unRTCDataChannelStats
instance IsRTCStats RTCDataChannelStats
instance IsGObject RTCDataChannelStats where
typeGType _ = gTypeRTCDataChannelStats
{-# INLINE typeGType #-}
noRTCDataChannelStats :: Maybe RTCDataChannelStats
noRTCDataChannelStats = Nothing
{-# INLINE noRTCDataChannelStats #-}
gTypeRTCDataChannelStats :: JSM GType
gTypeRTCDataChannelStats = GType . Object <$> jsg "RTCDataChannelStats"
newtype RTCIceCandidate = RTCIceCandidate { unRTCIceCandidate :: JSVal }
instance PToJSVal RTCIceCandidate where
pToJSVal = unRTCIceCandidate
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCIceCandidate where
pFromJSVal = RTCIceCandidate
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCIceCandidate where
toJSVal = return . unRTCIceCandidate
{-# INLINE toJSVal #-}
instance FromJSVal RTCIceCandidate where
fromJSVal v = fmap RTCIceCandidate <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCIceCandidate
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCIceCandidate where
makeObject = makeObject . unRTCIceCandidate
instance IsGObject RTCIceCandidate where
typeGType _ = gTypeRTCIceCandidate
{-# INLINE typeGType #-}
noRTCIceCandidate :: Maybe RTCIceCandidate
noRTCIceCandidate = Nothing
{-# INLINE noRTCIceCandidate #-}
gTypeRTCIceCandidate :: JSM GType
gTypeRTCIceCandidate = GType . Object <$> jsg "RTCIceCandidate"
newtype RTCIceCandidateEvent = RTCIceCandidateEvent { unRTCIceCandidateEvent :: JSVal }
instance PToJSVal RTCIceCandidateEvent where
pToJSVal = unRTCIceCandidateEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCIceCandidateEvent where
pFromJSVal = RTCIceCandidateEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCIceCandidateEvent where
toJSVal = return . unRTCIceCandidateEvent
{-# INLINE toJSVal #-}
instance FromJSVal RTCIceCandidateEvent where
fromJSVal v = fmap RTCIceCandidateEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCIceCandidateEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCIceCandidateEvent where
makeObject = makeObject . unRTCIceCandidateEvent
instance IsEvent RTCIceCandidateEvent
instance IsGObject RTCIceCandidateEvent where
typeGType _ = gTypeRTCIceCandidateEvent
{-# INLINE typeGType #-}
noRTCIceCandidateEvent :: Maybe RTCIceCandidateEvent
noRTCIceCandidateEvent = Nothing
{-# INLINE noRTCIceCandidateEvent #-}
gTypeRTCIceCandidateEvent :: JSM GType
gTypeRTCIceCandidateEvent = GType . Object <$> jsg "RTCIceCandidateEvent"
newtype RTCIceCandidateInit = RTCIceCandidateInit { unRTCIceCandidateInit :: JSVal }
instance PToJSVal RTCIceCandidateInit where
pToJSVal = unRTCIceCandidateInit
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCIceCandidateInit where
pFromJSVal = RTCIceCandidateInit
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCIceCandidateInit where
toJSVal = return . unRTCIceCandidateInit
{-# INLINE toJSVal #-}
instance FromJSVal RTCIceCandidateInit where
fromJSVal v = fmap RTCIceCandidateInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCIceCandidateInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCIceCandidateInit where
makeObject = makeObject . unRTCIceCandidateInit
instance IsGObject RTCIceCandidateInit where
typeGType _ = gTypeRTCIceCandidateInit
{-# INLINE typeGType #-}
noRTCIceCandidateInit :: Maybe RTCIceCandidateInit
noRTCIceCandidateInit = Nothing
{-# INLINE noRTCIceCandidateInit #-}
gTypeRTCIceCandidateInit :: JSM GType
gTypeRTCIceCandidateInit = GType . Object <$> jsg "RTCIceCandidateInit"
newtype RTCIceServer = RTCIceServer { unRTCIceServer :: JSVal }
instance PToJSVal RTCIceServer where
pToJSVal = unRTCIceServer
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCIceServer where
pFromJSVal = RTCIceServer
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCIceServer where
toJSVal = return . unRTCIceServer
{-# INLINE toJSVal #-}
instance FromJSVal RTCIceServer where
fromJSVal v = fmap RTCIceServer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCIceServer
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCIceServer where
makeObject = makeObject . unRTCIceServer
instance IsGObject RTCIceServer where
typeGType _ = gTypeRTCIceServer
{-# INLINE typeGType #-}
noRTCIceServer :: Maybe RTCIceServer
noRTCIceServer = Nothing
{-# INLINE noRTCIceServer #-}
gTypeRTCIceServer :: JSM GType
gTypeRTCIceServer = GType . Object <$> jsg "RTCIceServer"
newtype RTCIceTransport = RTCIceTransport { unRTCIceTransport :: JSVal }
instance PToJSVal RTCIceTransport where
pToJSVal = unRTCIceTransport
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCIceTransport where
pFromJSVal = RTCIceTransport
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCIceTransport where
toJSVal = return . unRTCIceTransport
{-# INLINE toJSVal #-}
instance FromJSVal RTCIceTransport where
fromJSVal v = fmap RTCIceTransport <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCIceTransport
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCIceTransport where
makeObject = makeObject . unRTCIceTransport
instance IsGObject RTCIceTransport where
typeGType _ = gTypeRTCIceTransport
{-# INLINE typeGType #-}
noRTCIceTransport :: Maybe RTCIceTransport
noRTCIceTransport = Nothing
{-# INLINE noRTCIceTransport #-}
gTypeRTCIceTransport :: JSM GType
gTypeRTCIceTransport = GType . Object <$> jsg "RTCIceTransport"
newtype RTCInboundRTPStreamStats = RTCInboundRTPStreamStats { unRTCInboundRTPStreamStats :: JSVal }
instance PToJSVal RTCInboundRTPStreamStats where
pToJSVal = unRTCInboundRTPStreamStats
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCInboundRTPStreamStats where
pFromJSVal = RTCInboundRTPStreamStats
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCInboundRTPStreamStats where
toJSVal = return . unRTCInboundRTPStreamStats
{-# INLINE toJSVal #-}
instance FromJSVal RTCInboundRTPStreamStats where
fromJSVal v = fmap RTCInboundRTPStreamStats <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCInboundRTPStreamStats
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCInboundRTPStreamStats where
makeObject = makeObject . unRTCInboundRTPStreamStats
instance IsRTCRTPStreamStats RTCInboundRTPStreamStats
instance IsRTCStats RTCInboundRTPStreamStats
instance IsGObject RTCInboundRTPStreamStats where
typeGType _ = gTypeRTCInboundRTPStreamStats
{-# INLINE typeGType #-}
noRTCInboundRTPStreamStats :: Maybe RTCInboundRTPStreamStats
noRTCInboundRTPStreamStats = Nothing
{-# INLINE noRTCInboundRTPStreamStats #-}
gTypeRTCInboundRTPStreamStats :: JSM GType
gTypeRTCInboundRTPStreamStats = GType . Object <$> jsg "RTCInboundRTPStreamStats"
newtype RTCMediaStreamTrackStats = RTCMediaStreamTrackStats { unRTCMediaStreamTrackStats :: JSVal }
instance PToJSVal RTCMediaStreamTrackStats where
pToJSVal = unRTCMediaStreamTrackStats
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCMediaStreamTrackStats where
pFromJSVal = RTCMediaStreamTrackStats
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCMediaStreamTrackStats where
toJSVal = return . unRTCMediaStreamTrackStats
{-# INLINE toJSVal #-}
instance FromJSVal RTCMediaStreamTrackStats where
fromJSVal v = fmap RTCMediaStreamTrackStats <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCMediaStreamTrackStats
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCMediaStreamTrackStats where
makeObject = makeObject . unRTCMediaStreamTrackStats
instance IsRTCStats RTCMediaStreamTrackStats
instance IsGObject RTCMediaStreamTrackStats where
typeGType _ = gTypeRTCMediaStreamTrackStats
{-# INLINE typeGType #-}
noRTCMediaStreamTrackStats :: Maybe RTCMediaStreamTrackStats
noRTCMediaStreamTrackStats = Nothing
{-# INLINE noRTCMediaStreamTrackStats #-}
gTypeRTCMediaStreamTrackStats :: JSM GType
gTypeRTCMediaStreamTrackStats = GType . Object <$> jsg "RTCMediaStreamTrackStats"
newtype RTCOfferAnswerOptions = RTCOfferAnswerOptions { unRTCOfferAnswerOptions :: JSVal }
instance PToJSVal RTCOfferAnswerOptions where
pToJSVal = unRTCOfferAnswerOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCOfferAnswerOptions where
pFromJSVal = RTCOfferAnswerOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCOfferAnswerOptions where
toJSVal = return . unRTCOfferAnswerOptions
{-# INLINE toJSVal #-}
instance FromJSVal RTCOfferAnswerOptions where
fromJSVal v = fmap RTCOfferAnswerOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCOfferAnswerOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCOfferAnswerOptions where
makeObject = makeObject . unRTCOfferAnswerOptions
class (IsGObject o) => IsRTCOfferAnswerOptions o
toRTCOfferAnswerOptions :: IsRTCOfferAnswerOptions o => o -> RTCOfferAnswerOptions
toRTCOfferAnswerOptions = RTCOfferAnswerOptions . coerce
instance IsRTCOfferAnswerOptions RTCOfferAnswerOptions
instance IsGObject RTCOfferAnswerOptions where
typeGType _ = gTypeRTCOfferAnswerOptions
{-# INLINE typeGType #-}
noRTCOfferAnswerOptions :: Maybe RTCOfferAnswerOptions
noRTCOfferAnswerOptions = Nothing
{-# INLINE noRTCOfferAnswerOptions #-}
gTypeRTCOfferAnswerOptions :: JSM GType
gTypeRTCOfferAnswerOptions = GType . Object <$> jsg "RTCOfferAnswerOptions"
newtype RTCOfferOptions = RTCOfferOptions { unRTCOfferOptions :: JSVal }
instance PToJSVal RTCOfferOptions where
pToJSVal = unRTCOfferOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCOfferOptions where
pFromJSVal = RTCOfferOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCOfferOptions where
toJSVal = return . unRTCOfferOptions
{-# INLINE toJSVal #-}
instance FromJSVal RTCOfferOptions where
fromJSVal v = fmap RTCOfferOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCOfferOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCOfferOptions where
makeObject = makeObject . unRTCOfferOptions
instance IsRTCOfferAnswerOptions RTCOfferOptions
instance IsGObject RTCOfferOptions where
typeGType _ = gTypeRTCOfferOptions
{-# INLINE typeGType #-}
noRTCOfferOptions :: Maybe RTCOfferOptions
noRTCOfferOptions = Nothing
{-# INLINE noRTCOfferOptions #-}
gTypeRTCOfferOptions :: JSM GType
gTypeRTCOfferOptions = GType . Object <$> jsg "RTCOfferOptions"
newtype RTCOutboundRTPStreamStats = RTCOutboundRTPStreamStats { unRTCOutboundRTPStreamStats :: JSVal }
instance PToJSVal RTCOutboundRTPStreamStats where
pToJSVal = unRTCOutboundRTPStreamStats
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCOutboundRTPStreamStats where
pFromJSVal = RTCOutboundRTPStreamStats
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCOutboundRTPStreamStats where
toJSVal = return . unRTCOutboundRTPStreamStats
{-# INLINE toJSVal #-}
instance FromJSVal RTCOutboundRTPStreamStats where
fromJSVal v = fmap RTCOutboundRTPStreamStats <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCOutboundRTPStreamStats
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCOutboundRTPStreamStats where
makeObject = makeObject . unRTCOutboundRTPStreamStats
instance IsRTCRTPStreamStats RTCOutboundRTPStreamStats
instance IsRTCStats RTCOutboundRTPStreamStats
instance IsGObject RTCOutboundRTPStreamStats where
typeGType _ = gTypeRTCOutboundRTPStreamStats
{-# INLINE typeGType #-}
noRTCOutboundRTPStreamStats :: Maybe RTCOutboundRTPStreamStats
noRTCOutboundRTPStreamStats = Nothing
{-# INLINE noRTCOutboundRTPStreamStats #-}
gTypeRTCOutboundRTPStreamStats :: JSM GType
gTypeRTCOutboundRTPStreamStats = GType . Object <$> jsg "RTCOutboundRTPStreamStats"
newtype RTCPeerConnection = RTCPeerConnection { unRTCPeerConnection :: JSVal }
instance PToJSVal RTCPeerConnection where
pToJSVal = unRTCPeerConnection
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCPeerConnection where
pFromJSVal = RTCPeerConnection
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCPeerConnection where
toJSVal = return . unRTCPeerConnection
{-# INLINE toJSVal #-}
instance FromJSVal RTCPeerConnection where
fromJSVal v = fmap RTCPeerConnection <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCPeerConnection
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCPeerConnection where
makeObject = makeObject . unRTCPeerConnection
instance IsEventTarget RTCPeerConnection
instance IsGObject RTCPeerConnection where
typeGType _ = gTypeRTCPeerConnection
{-# INLINE typeGType #-}
noRTCPeerConnection :: Maybe RTCPeerConnection
noRTCPeerConnection = Nothing
{-# INLINE noRTCPeerConnection #-}
gTypeRTCPeerConnection :: JSM GType
gTypeRTCPeerConnection = GType . Object <$> jsg "webkitRTCPeerConnection"
newtype RTCPeerConnectionIceEvent = RTCPeerConnectionIceEvent { unRTCPeerConnectionIceEvent :: JSVal }
instance PToJSVal RTCPeerConnectionIceEvent where
pToJSVal = unRTCPeerConnectionIceEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCPeerConnectionIceEvent where
pFromJSVal = RTCPeerConnectionIceEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCPeerConnectionIceEvent where
toJSVal = return . unRTCPeerConnectionIceEvent
{-# INLINE toJSVal #-}
instance FromJSVal RTCPeerConnectionIceEvent where
fromJSVal v = fmap RTCPeerConnectionIceEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCPeerConnectionIceEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCPeerConnectionIceEvent where
makeObject = makeObject . unRTCPeerConnectionIceEvent
instance IsEvent RTCPeerConnectionIceEvent
instance IsGObject RTCPeerConnectionIceEvent where
typeGType _ = gTypeRTCPeerConnectionIceEvent
{-# INLINE typeGType #-}
noRTCPeerConnectionIceEvent :: Maybe RTCPeerConnectionIceEvent
noRTCPeerConnectionIceEvent = Nothing
{-# INLINE noRTCPeerConnectionIceEvent #-}
gTypeRTCPeerConnectionIceEvent :: JSM GType
gTypeRTCPeerConnectionIceEvent = GType . Object <$> jsg "RTCPeerConnectionIceEvent"
newtype RTCRTPStreamStats = RTCRTPStreamStats { unRTCRTPStreamStats :: JSVal }
instance PToJSVal RTCRTPStreamStats where
pToJSVal = unRTCRTPStreamStats
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCRTPStreamStats where
pFromJSVal = RTCRTPStreamStats
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCRTPStreamStats where
toJSVal = return . unRTCRTPStreamStats
{-# INLINE toJSVal #-}
instance FromJSVal RTCRTPStreamStats where
fromJSVal v = fmap RTCRTPStreamStats <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCRTPStreamStats
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCRTPStreamStats where
makeObject = makeObject . unRTCRTPStreamStats
class (IsRTCStats o, IsGObject o) => IsRTCRTPStreamStats o
toRTCRTPStreamStats :: IsRTCRTPStreamStats o => o -> RTCRTPStreamStats
toRTCRTPStreamStats = RTCRTPStreamStats . coerce
instance IsRTCRTPStreamStats RTCRTPStreamStats
instance IsRTCStats RTCRTPStreamStats
instance IsGObject RTCRTPStreamStats where
typeGType _ = gTypeRTCRTPStreamStats
{-# INLINE typeGType #-}
noRTCRTPStreamStats :: Maybe RTCRTPStreamStats
noRTCRTPStreamStats = Nothing
{-# INLINE noRTCRTPStreamStats #-}
gTypeRTCRTPStreamStats :: JSM GType
gTypeRTCRTPStreamStats = GType . Object <$> jsg "RTCRTPStreamStats"
newtype RTCRtpCodecParameters = RTCRtpCodecParameters { unRTCRtpCodecParameters :: JSVal }
instance PToJSVal RTCRtpCodecParameters where
pToJSVal = unRTCRtpCodecParameters
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCRtpCodecParameters where
pFromJSVal = RTCRtpCodecParameters
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCRtpCodecParameters where
toJSVal = return . unRTCRtpCodecParameters
{-# INLINE toJSVal #-}
instance FromJSVal RTCRtpCodecParameters where
fromJSVal v = fmap RTCRtpCodecParameters <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCRtpCodecParameters
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCRtpCodecParameters where
makeObject = makeObject . unRTCRtpCodecParameters
instance IsGObject RTCRtpCodecParameters where
typeGType _ = gTypeRTCRtpCodecParameters
{-# INLINE typeGType #-}
noRTCRtpCodecParameters :: Maybe RTCRtpCodecParameters
noRTCRtpCodecParameters = Nothing
{-# INLINE noRTCRtpCodecParameters #-}
gTypeRTCRtpCodecParameters :: JSM GType
gTypeRTCRtpCodecParameters = GType . Object <$> jsg "RTCRtpCodecParameters"
newtype RTCRtpEncodingParameters = RTCRtpEncodingParameters { unRTCRtpEncodingParameters :: JSVal }
instance PToJSVal RTCRtpEncodingParameters where
pToJSVal = unRTCRtpEncodingParameters
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCRtpEncodingParameters where
pFromJSVal = RTCRtpEncodingParameters
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCRtpEncodingParameters where
toJSVal = return . unRTCRtpEncodingParameters
{-# INLINE toJSVal #-}
instance FromJSVal RTCRtpEncodingParameters where
fromJSVal v = fmap RTCRtpEncodingParameters <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCRtpEncodingParameters
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCRtpEncodingParameters where
makeObject = makeObject . unRTCRtpEncodingParameters
instance IsGObject RTCRtpEncodingParameters where
typeGType _ = gTypeRTCRtpEncodingParameters
{-# INLINE typeGType #-}
noRTCRtpEncodingParameters :: Maybe RTCRtpEncodingParameters
noRTCRtpEncodingParameters = Nothing
{-# INLINE noRTCRtpEncodingParameters #-}
gTypeRTCRtpEncodingParameters :: JSM GType
gTypeRTCRtpEncodingParameters = GType . Object <$> jsg "RTCRtpEncodingParameters"
newtype RTCRtpFecParameters = RTCRtpFecParameters { unRTCRtpFecParameters :: JSVal }
instance PToJSVal RTCRtpFecParameters where
pToJSVal = unRTCRtpFecParameters
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCRtpFecParameters where
pFromJSVal = RTCRtpFecParameters
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCRtpFecParameters where
toJSVal = return . unRTCRtpFecParameters
{-# INLINE toJSVal #-}
instance FromJSVal RTCRtpFecParameters where
fromJSVal v = fmap RTCRtpFecParameters <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCRtpFecParameters
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCRtpFecParameters where
makeObject = makeObject . unRTCRtpFecParameters
instance IsGObject RTCRtpFecParameters where
typeGType _ = gTypeRTCRtpFecParameters
{-# INLINE typeGType #-}
noRTCRtpFecParameters :: Maybe RTCRtpFecParameters
noRTCRtpFecParameters = Nothing
{-# INLINE noRTCRtpFecParameters #-}
gTypeRTCRtpFecParameters :: JSM GType
gTypeRTCRtpFecParameters = GType . Object <$> jsg "RTCRtpFecParameters"
newtype RTCRtpHeaderExtensionParameters = RTCRtpHeaderExtensionParameters { unRTCRtpHeaderExtensionParameters :: JSVal }
instance PToJSVal RTCRtpHeaderExtensionParameters where
pToJSVal = unRTCRtpHeaderExtensionParameters
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCRtpHeaderExtensionParameters where
pFromJSVal = RTCRtpHeaderExtensionParameters
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCRtpHeaderExtensionParameters where
toJSVal = return . unRTCRtpHeaderExtensionParameters
{-# INLINE toJSVal #-}
instance FromJSVal RTCRtpHeaderExtensionParameters where
fromJSVal v = fmap RTCRtpHeaderExtensionParameters <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCRtpHeaderExtensionParameters
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCRtpHeaderExtensionParameters where
makeObject = makeObject . unRTCRtpHeaderExtensionParameters
instance IsGObject RTCRtpHeaderExtensionParameters where
typeGType _ = gTypeRTCRtpHeaderExtensionParameters
{-# INLINE typeGType #-}
noRTCRtpHeaderExtensionParameters :: Maybe RTCRtpHeaderExtensionParameters
noRTCRtpHeaderExtensionParameters = Nothing
{-# INLINE noRTCRtpHeaderExtensionParameters #-}
gTypeRTCRtpHeaderExtensionParameters :: JSM GType
gTypeRTCRtpHeaderExtensionParameters = GType . Object <$> jsg "RTCRtpHeaderExtensionParameters"
newtype RTCRtpParameters = RTCRtpParameters { unRTCRtpParameters :: JSVal }
instance PToJSVal RTCRtpParameters where
pToJSVal = unRTCRtpParameters
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCRtpParameters where
pFromJSVal = RTCRtpParameters
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCRtpParameters where
toJSVal = return . unRTCRtpParameters
{-# INLINE toJSVal #-}
instance FromJSVal RTCRtpParameters where
fromJSVal v = fmap RTCRtpParameters <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCRtpParameters
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCRtpParameters where
makeObject = makeObject . unRTCRtpParameters
instance IsGObject RTCRtpParameters where
typeGType _ = gTypeRTCRtpParameters
{-# INLINE typeGType #-}
noRTCRtpParameters :: Maybe RTCRtpParameters
noRTCRtpParameters = Nothing
{-# INLINE noRTCRtpParameters #-}
gTypeRTCRtpParameters :: JSM GType
gTypeRTCRtpParameters = GType . Object <$> jsg "RTCRtpParameters"
newtype RTCRtpReceiver = RTCRtpReceiver { unRTCRtpReceiver :: JSVal }
instance PToJSVal RTCRtpReceiver where
pToJSVal = unRTCRtpReceiver
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCRtpReceiver where
pFromJSVal = RTCRtpReceiver
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCRtpReceiver where
toJSVal = return . unRTCRtpReceiver
{-# INLINE toJSVal #-}
instance FromJSVal RTCRtpReceiver where
fromJSVal v = fmap RTCRtpReceiver <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCRtpReceiver
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCRtpReceiver where
makeObject = makeObject . unRTCRtpReceiver
instance IsGObject RTCRtpReceiver where
typeGType _ = gTypeRTCRtpReceiver
{-# INLINE typeGType #-}
noRTCRtpReceiver :: Maybe RTCRtpReceiver
noRTCRtpReceiver = Nothing
{-# INLINE noRTCRtpReceiver #-}
gTypeRTCRtpReceiver :: JSM GType
gTypeRTCRtpReceiver = GType . Object <$> jsg "RTCRtpReceiver"
newtype RTCRtpRtxParameters = RTCRtpRtxParameters { unRTCRtpRtxParameters :: JSVal }
instance PToJSVal RTCRtpRtxParameters where
pToJSVal = unRTCRtpRtxParameters
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCRtpRtxParameters where
pFromJSVal = RTCRtpRtxParameters
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCRtpRtxParameters where
toJSVal = return . unRTCRtpRtxParameters
{-# INLINE toJSVal #-}
instance FromJSVal RTCRtpRtxParameters where
fromJSVal v = fmap RTCRtpRtxParameters <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCRtpRtxParameters
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCRtpRtxParameters where
makeObject = makeObject . unRTCRtpRtxParameters
instance IsGObject RTCRtpRtxParameters where
typeGType _ = gTypeRTCRtpRtxParameters
{-# INLINE typeGType #-}
noRTCRtpRtxParameters :: Maybe RTCRtpRtxParameters
noRTCRtpRtxParameters = Nothing
{-# INLINE noRTCRtpRtxParameters #-}
gTypeRTCRtpRtxParameters :: JSM GType
gTypeRTCRtpRtxParameters = GType . Object <$> jsg "RTCRtpRtxParameters"
newtype RTCRtpSender = RTCRtpSender { unRTCRtpSender :: JSVal }
instance PToJSVal RTCRtpSender where
pToJSVal = unRTCRtpSender
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCRtpSender where
pFromJSVal = RTCRtpSender
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCRtpSender where
toJSVal = return . unRTCRtpSender
{-# INLINE toJSVal #-}
instance FromJSVal RTCRtpSender where
fromJSVal v = fmap RTCRtpSender <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCRtpSender
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCRtpSender where
makeObject = makeObject . unRTCRtpSender
instance IsGObject RTCRtpSender where
typeGType _ = gTypeRTCRtpSender
{-# INLINE typeGType #-}
noRTCRtpSender :: Maybe RTCRtpSender
noRTCRtpSender = Nothing
{-# INLINE noRTCRtpSender #-}
gTypeRTCRtpSender :: JSM GType
gTypeRTCRtpSender = GType . Object <$> jsg "RTCRtpSender"
newtype RTCRtpTransceiver = RTCRtpTransceiver { unRTCRtpTransceiver :: JSVal }
instance PToJSVal RTCRtpTransceiver where
pToJSVal = unRTCRtpTransceiver
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCRtpTransceiver where
pFromJSVal = RTCRtpTransceiver
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCRtpTransceiver where
toJSVal = return . unRTCRtpTransceiver
{-# INLINE toJSVal #-}
instance FromJSVal RTCRtpTransceiver where
fromJSVal v = fmap RTCRtpTransceiver <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCRtpTransceiver
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCRtpTransceiver where
makeObject = makeObject . unRTCRtpTransceiver
instance IsGObject RTCRtpTransceiver where
typeGType _ = gTypeRTCRtpTransceiver
{-# INLINE typeGType #-}
noRTCRtpTransceiver :: Maybe RTCRtpTransceiver
noRTCRtpTransceiver = Nothing
{-# INLINE noRTCRtpTransceiver #-}
gTypeRTCRtpTransceiver :: JSM GType
gTypeRTCRtpTransceiver = GType . Object <$> jsg "RTCRtpTransceiver"
newtype RTCRtpTransceiverInit = RTCRtpTransceiverInit { unRTCRtpTransceiverInit :: JSVal }
instance PToJSVal RTCRtpTransceiverInit where
pToJSVal = unRTCRtpTransceiverInit
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCRtpTransceiverInit where
pFromJSVal = RTCRtpTransceiverInit
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCRtpTransceiverInit where
toJSVal = return . unRTCRtpTransceiverInit
{-# INLINE toJSVal #-}
instance FromJSVal RTCRtpTransceiverInit where
fromJSVal v = fmap RTCRtpTransceiverInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCRtpTransceiverInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCRtpTransceiverInit where
makeObject = makeObject . unRTCRtpTransceiverInit
instance IsGObject RTCRtpTransceiverInit where
typeGType _ = gTypeRTCRtpTransceiverInit
{-# INLINE typeGType #-}
noRTCRtpTransceiverInit :: Maybe RTCRtpTransceiverInit
noRTCRtpTransceiverInit = Nothing
{-# INLINE noRTCRtpTransceiverInit #-}
gTypeRTCRtpTransceiverInit :: JSM GType
gTypeRTCRtpTransceiverInit = GType . Object <$> jsg "RTCRtpTransceiverInit"
newtype RTCSessionDescription = RTCSessionDescription { unRTCSessionDescription :: JSVal }
instance PToJSVal RTCSessionDescription where
pToJSVal = unRTCSessionDescription
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCSessionDescription where
pFromJSVal = RTCSessionDescription
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCSessionDescription where
toJSVal = return . unRTCSessionDescription
{-# INLINE toJSVal #-}
instance FromJSVal RTCSessionDescription where
fromJSVal v = fmap RTCSessionDescription <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCSessionDescription
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCSessionDescription where
makeObject = makeObject . unRTCSessionDescription
instance IsGObject RTCSessionDescription where
typeGType _ = gTypeRTCSessionDescription
{-# INLINE typeGType #-}
noRTCSessionDescription :: Maybe RTCSessionDescription
noRTCSessionDescription = Nothing
{-# INLINE noRTCSessionDescription #-}
gTypeRTCSessionDescription :: JSM GType
gTypeRTCSessionDescription = GType . Object <$> jsg "RTCSessionDescription"
newtype RTCSessionDescriptionInit = RTCSessionDescriptionInit { unRTCSessionDescriptionInit :: JSVal }
instance PToJSVal RTCSessionDescriptionInit where
pToJSVal = unRTCSessionDescriptionInit
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCSessionDescriptionInit where
pFromJSVal = RTCSessionDescriptionInit
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCSessionDescriptionInit where
toJSVal = return . unRTCSessionDescriptionInit
{-# INLINE toJSVal #-}
instance FromJSVal RTCSessionDescriptionInit where
fromJSVal v = fmap RTCSessionDescriptionInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCSessionDescriptionInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCSessionDescriptionInit where
makeObject = makeObject . unRTCSessionDescriptionInit
instance IsGObject RTCSessionDescriptionInit where
typeGType _ = gTypeRTCSessionDescriptionInit
{-# INLINE typeGType #-}
noRTCSessionDescriptionInit :: Maybe RTCSessionDescriptionInit
noRTCSessionDescriptionInit = Nothing
{-# INLINE noRTCSessionDescriptionInit #-}
gTypeRTCSessionDescriptionInit :: JSM GType
gTypeRTCSessionDescriptionInit = GType . Object <$> jsg "RTCSessionDescriptionInit"
newtype RTCStats = RTCStats { unRTCStats :: JSVal }
instance PToJSVal RTCStats where
pToJSVal = unRTCStats
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCStats where
pFromJSVal = RTCStats
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCStats where
toJSVal = return . unRTCStats
{-# INLINE toJSVal #-}
instance FromJSVal RTCStats where
fromJSVal v = fmap RTCStats <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCStats
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCStats where
makeObject = makeObject . unRTCStats
class (IsGObject o) => IsRTCStats o
toRTCStats :: IsRTCStats o => o -> RTCStats
toRTCStats = RTCStats . coerce
instance IsRTCStats RTCStats
instance IsGObject RTCStats where
typeGType _ = gTypeRTCStats
{-# INLINE typeGType #-}
noRTCStats :: Maybe RTCStats
noRTCStats = Nothing
{-# INLINE noRTCStats #-}
gTypeRTCStats :: JSM GType
gTypeRTCStats = GType . Object <$> jsg "RTCStats"
newtype RTCStatsReport = RTCStatsReport { unRTCStatsReport :: JSVal }
instance PToJSVal RTCStatsReport where
pToJSVal = unRTCStatsReport
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCStatsReport where
pFromJSVal = RTCStatsReport
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCStatsReport where
toJSVal = return . unRTCStatsReport
{-# INLINE toJSVal #-}
instance FromJSVal RTCStatsReport where
fromJSVal v = fmap RTCStatsReport <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCStatsReport
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCStatsReport where
makeObject = makeObject . unRTCStatsReport
instance IsGObject RTCStatsReport where
typeGType _ = gTypeRTCStatsReport
{-# INLINE typeGType #-}
noRTCStatsReport :: Maybe RTCStatsReport
noRTCStatsReport = Nothing
{-# INLINE noRTCStatsReport #-}
gTypeRTCStatsReport :: JSM GType
gTypeRTCStatsReport = GType . Object <$> jsg "RTCStatsReport"
newtype RTCTrackEvent = RTCTrackEvent { unRTCTrackEvent :: JSVal }
instance PToJSVal RTCTrackEvent where
pToJSVal = unRTCTrackEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCTrackEvent where
pFromJSVal = RTCTrackEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCTrackEvent where
toJSVal = return . unRTCTrackEvent
{-# INLINE toJSVal #-}
instance FromJSVal RTCTrackEvent where
fromJSVal v = fmap RTCTrackEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCTrackEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCTrackEvent where
makeObject = makeObject . unRTCTrackEvent
instance IsEvent RTCTrackEvent
instance IsGObject RTCTrackEvent where
typeGType _ = gTypeRTCTrackEvent
{-# INLINE typeGType #-}
noRTCTrackEvent :: Maybe RTCTrackEvent
noRTCTrackEvent = Nothing
{-# INLINE noRTCTrackEvent #-}
gTypeRTCTrackEvent :: JSM GType
gTypeRTCTrackEvent = GType . Object <$> jsg "RTCTrackEvent"
newtype RTCTrackEventInit = RTCTrackEventInit { unRTCTrackEventInit :: JSVal }
instance PToJSVal RTCTrackEventInit where
pToJSVal = unRTCTrackEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal RTCTrackEventInit where
pFromJSVal = RTCTrackEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal RTCTrackEventInit where
toJSVal = return . unRTCTrackEventInit
{-# INLINE toJSVal #-}
instance FromJSVal RTCTrackEventInit where
fromJSVal v = fmap RTCTrackEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RTCTrackEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RTCTrackEventInit where
makeObject = makeObject . unRTCTrackEventInit
instance IsEventInit RTCTrackEventInit
instance IsGObject RTCTrackEventInit where
typeGType _ = gTypeRTCTrackEventInit
{-# INLINE typeGType #-}
noRTCTrackEventInit :: Maybe RTCTrackEventInit
noRTCTrackEventInit = Nothing
{-# INLINE noRTCTrackEventInit #-}
gTypeRTCTrackEventInit :: JSM GType
gTypeRTCTrackEventInit = GType . Object <$> jsg "RTCTrackEventInit"
newtype RadioNodeList = RadioNodeList { unRadioNodeList :: JSVal }
instance PToJSVal RadioNodeList where
pToJSVal = unRadioNodeList
{-# INLINE pToJSVal #-}
instance PFromJSVal RadioNodeList where
pFromJSVal = RadioNodeList
{-# INLINE pFromJSVal #-}
instance ToJSVal RadioNodeList where
toJSVal = return . unRadioNodeList
{-# INLINE toJSVal #-}
instance FromJSVal RadioNodeList where
fromJSVal v = fmap RadioNodeList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RadioNodeList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RadioNodeList where
makeObject = makeObject . unRadioNodeList
instance IsNodeList RadioNodeList
instance IsGObject RadioNodeList where
typeGType _ = gTypeRadioNodeList
{-# INLINE typeGType #-}
noRadioNodeList :: Maybe RadioNodeList
noRadioNodeList = Nothing
{-# INLINE noRadioNodeList #-}
gTypeRadioNodeList :: JSM GType
gTypeRadioNodeList = GType . Object <$> jsg "RadioNodeList"
newtype Range = Range { unRange :: JSVal }
instance PToJSVal Range where
pToJSVal = unRange
{-# INLINE pToJSVal #-}
instance PFromJSVal Range where
pFromJSVal = Range
{-# INLINE pFromJSVal #-}
instance ToJSVal Range where
toJSVal = return . unRange
{-# INLINE toJSVal #-}
instance FromJSVal Range where
fromJSVal v = fmap Range <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Range
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Range where
makeObject = makeObject . unRange
instance IsGObject Range where
typeGType _ = gTypeRange
{-# INLINE typeGType #-}
noRange :: Maybe Range
noRange = Nothing
{-# INLINE noRange #-}
gTypeRange :: JSM GType
gTypeRange = GType . Object <$> jsg "Range"
newtype ReadableByteStreamController = ReadableByteStreamController { unReadableByteStreamController :: JSVal }
instance PToJSVal ReadableByteStreamController where
pToJSVal = unReadableByteStreamController
{-# INLINE pToJSVal #-}
instance PFromJSVal ReadableByteStreamController where
pFromJSVal = ReadableByteStreamController
{-# INLINE pFromJSVal #-}
instance ToJSVal ReadableByteStreamController where
toJSVal = return . unReadableByteStreamController
{-# INLINE toJSVal #-}
instance FromJSVal ReadableByteStreamController where
fromJSVal v = fmap ReadableByteStreamController <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ReadableByteStreamController
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ReadableByteStreamController where
makeObject = makeObject . unReadableByteStreamController
instance IsGObject ReadableByteStreamController where
typeGType _ = gTypeReadableByteStreamController
{-# INLINE typeGType #-}
noReadableByteStreamController :: Maybe ReadableByteStreamController
noReadableByteStreamController = Nothing
{-# INLINE noReadableByteStreamController #-}
gTypeReadableByteStreamController :: JSM GType
gTypeReadableByteStreamController = GType . Object <$> jsg "ReadableByteStreamController"
newtype ReadableStream = ReadableStream { unReadableStream :: JSVal }
instance PToJSVal ReadableStream where
pToJSVal = unReadableStream
{-# INLINE pToJSVal #-}
instance PFromJSVal ReadableStream where
pFromJSVal = ReadableStream
{-# INLINE pFromJSVal #-}
instance ToJSVal ReadableStream where
toJSVal = return . unReadableStream
{-# INLINE toJSVal #-}
instance FromJSVal ReadableStream where
fromJSVal v = fmap ReadableStream <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ReadableStream
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ReadableStream where
makeObject = makeObject . unReadableStream
instance IsGObject ReadableStream where
typeGType _ = gTypeReadableStream
{-# INLINE typeGType #-}
noReadableStream :: Maybe ReadableStream
noReadableStream = Nothing
{-# INLINE noReadableStream #-}
gTypeReadableStream :: JSM GType
gTypeReadableStream = GType . Object <$> jsg "ReadableStream"
newtype ReadableStreamBYOBReader = ReadableStreamBYOBReader { unReadableStreamBYOBReader :: JSVal }
instance PToJSVal ReadableStreamBYOBReader where
pToJSVal = unReadableStreamBYOBReader
{-# INLINE pToJSVal #-}
instance PFromJSVal ReadableStreamBYOBReader where
pFromJSVal = ReadableStreamBYOBReader
{-# INLINE pFromJSVal #-}
instance ToJSVal ReadableStreamBYOBReader where
toJSVal = return . unReadableStreamBYOBReader
{-# INLINE toJSVal #-}
instance FromJSVal ReadableStreamBYOBReader where
fromJSVal v = fmap ReadableStreamBYOBReader <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ReadableStreamBYOBReader
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ReadableStreamBYOBReader where
makeObject = makeObject . unReadableStreamBYOBReader
instance IsGObject ReadableStreamBYOBReader where
typeGType _ = gTypeReadableStreamBYOBReader
{-# INLINE typeGType #-}
noReadableStreamBYOBReader :: Maybe ReadableStreamBYOBReader
noReadableStreamBYOBReader = Nothing
{-# INLINE noReadableStreamBYOBReader #-}
gTypeReadableStreamBYOBReader :: JSM GType
gTypeReadableStreamBYOBReader = GType . Object <$> jsg "ReadableStreamBYOBReader"
newtype ReadableStreamBYOBRequest = ReadableStreamBYOBRequest { unReadableStreamBYOBRequest :: JSVal }
instance PToJSVal ReadableStreamBYOBRequest where
pToJSVal = unReadableStreamBYOBRequest
{-# INLINE pToJSVal #-}
instance PFromJSVal ReadableStreamBYOBRequest where
pFromJSVal = ReadableStreamBYOBRequest
{-# INLINE pFromJSVal #-}
instance ToJSVal ReadableStreamBYOBRequest where
toJSVal = return . unReadableStreamBYOBRequest
{-# INLINE toJSVal #-}
instance FromJSVal ReadableStreamBYOBRequest where
fromJSVal v = fmap ReadableStreamBYOBRequest <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ReadableStreamBYOBRequest
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ReadableStreamBYOBRequest where
makeObject = makeObject . unReadableStreamBYOBRequest
instance IsGObject ReadableStreamBYOBRequest where
typeGType _ = gTypeReadableStreamBYOBRequest
{-# INLINE typeGType #-}
noReadableStreamBYOBRequest :: Maybe ReadableStreamBYOBRequest
noReadableStreamBYOBRequest = Nothing
{-# INLINE noReadableStreamBYOBRequest #-}
gTypeReadableStreamBYOBRequest :: JSM GType
gTypeReadableStreamBYOBRequest = GType . Object <$> jsg "ReadableStreamBYOBRequest"
newtype ReadableStreamDefaultController = ReadableStreamDefaultController { unReadableStreamDefaultController :: JSVal }
instance PToJSVal ReadableStreamDefaultController where
pToJSVal = unReadableStreamDefaultController
{-# INLINE pToJSVal #-}
instance PFromJSVal ReadableStreamDefaultController where
pFromJSVal = ReadableStreamDefaultController
{-# INLINE pFromJSVal #-}
instance ToJSVal ReadableStreamDefaultController where
toJSVal = return . unReadableStreamDefaultController
{-# INLINE toJSVal #-}
instance FromJSVal ReadableStreamDefaultController where
fromJSVal v = fmap ReadableStreamDefaultController <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ReadableStreamDefaultController
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ReadableStreamDefaultController where
makeObject = makeObject . unReadableStreamDefaultController
instance IsGObject ReadableStreamDefaultController where
typeGType _ = gTypeReadableStreamDefaultController
{-# INLINE typeGType #-}
noReadableStreamDefaultController :: Maybe ReadableStreamDefaultController
noReadableStreamDefaultController = Nothing
{-# INLINE noReadableStreamDefaultController #-}
gTypeReadableStreamDefaultController :: JSM GType
gTypeReadableStreamDefaultController = GType . Object <$> jsg "ReadableStreamDefaultController"
newtype ReadableStreamDefaultReader = ReadableStreamDefaultReader { unReadableStreamDefaultReader :: JSVal }
instance PToJSVal ReadableStreamDefaultReader where
pToJSVal = unReadableStreamDefaultReader
{-# INLINE pToJSVal #-}
instance PFromJSVal ReadableStreamDefaultReader where
pFromJSVal = ReadableStreamDefaultReader
{-# INLINE pFromJSVal #-}
instance ToJSVal ReadableStreamDefaultReader where
toJSVal = return . unReadableStreamDefaultReader
{-# INLINE toJSVal #-}
instance FromJSVal ReadableStreamDefaultReader where
fromJSVal v = fmap ReadableStreamDefaultReader <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ReadableStreamDefaultReader
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ReadableStreamDefaultReader where
makeObject = makeObject . unReadableStreamDefaultReader
instance IsGObject ReadableStreamDefaultReader where
typeGType _ = gTypeReadableStreamDefaultReader
{-# INLINE typeGType #-}
noReadableStreamDefaultReader :: Maybe ReadableStreamDefaultReader
noReadableStreamDefaultReader = Nothing
{-# INLINE noReadableStreamDefaultReader #-}
gTypeReadableStreamDefaultReader :: JSM GType
gTypeReadableStreamDefaultReader = GType . Object <$> jsg "ReadableStreamDefaultReader"
newtype ReadableStreamSource = ReadableStreamSource { unReadableStreamSource :: JSVal }
instance PToJSVal ReadableStreamSource where
pToJSVal = unReadableStreamSource
{-# INLINE pToJSVal #-}
instance PFromJSVal ReadableStreamSource where
pFromJSVal = ReadableStreamSource
{-# INLINE pFromJSVal #-}
instance ToJSVal ReadableStreamSource where
toJSVal = return . unReadableStreamSource
{-# INLINE toJSVal #-}
instance FromJSVal ReadableStreamSource where
fromJSVal v = fmap ReadableStreamSource <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ReadableStreamSource
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ReadableStreamSource where
makeObject = makeObject . unReadableStreamSource
instance IsGObject ReadableStreamSource where
typeGType _ = gTypeReadableStreamSource
{-# INLINE typeGType #-}
noReadableStreamSource :: Maybe ReadableStreamSource
noReadableStreamSource = Nothing
{-# INLINE noReadableStreamSource #-}
gTypeReadableStreamSource :: JSM GType
gTypeReadableStreamSource = GType . Object <$> jsg "ReadableStreamSource"
newtype Rect = Rect { unRect :: JSVal }
instance PToJSVal Rect where
pToJSVal = unRect
{-# INLINE pToJSVal #-}
instance PFromJSVal Rect where
pFromJSVal = Rect
{-# INLINE pFromJSVal #-}
instance ToJSVal Rect where
toJSVal = return . unRect
{-# INLINE toJSVal #-}
instance FromJSVal Rect where
fromJSVal v = fmap Rect <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Rect
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Rect where
makeObject = makeObject . unRect
instance IsGObject Rect where
typeGType _ = gTypeRect
{-# INLINE typeGType #-}
noRect :: Maybe Rect
noRect = Nothing
{-# INLINE noRect #-}
gTypeRect :: JSM GType
gTypeRect = GType . Object <$> jsg "Rect"
newtype Request = Request { unRequest :: JSVal }
instance PToJSVal Request where
pToJSVal = unRequest
{-# INLINE pToJSVal #-}
instance PFromJSVal Request where
pFromJSVal = Request
{-# INLINE pFromJSVal #-}
instance ToJSVal Request where
toJSVal = return . unRequest
{-# INLINE toJSVal #-}
instance FromJSVal Request where
fromJSVal v = fmap Request <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Request
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Request where
makeObject = makeObject . unRequest
instance IsBody Request
instance IsGObject Request where
typeGType _ = gTypeRequest
{-# INLINE typeGType #-}
noRequest :: Maybe Request
noRequest = Nothing
{-# INLINE noRequest #-}
gTypeRequest :: JSM GType
gTypeRequest = GType . Object <$> jsg "Request"
newtype RequestInit = RequestInit { unRequestInit :: JSVal }
instance PToJSVal RequestInit where
pToJSVal = unRequestInit
{-# INLINE pToJSVal #-}
instance PFromJSVal RequestInit where
pFromJSVal = RequestInit
{-# INLINE pFromJSVal #-}
instance ToJSVal RequestInit where
toJSVal = return . unRequestInit
{-# INLINE toJSVal #-}
instance FromJSVal RequestInit where
fromJSVal v = fmap RequestInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RequestInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RequestInit where
makeObject = makeObject . unRequestInit
instance IsGObject RequestInit where
typeGType _ = gTypeRequestInit
{-# INLINE typeGType #-}
noRequestInit :: Maybe RequestInit
noRequestInit = Nothing
{-# INLINE noRequestInit #-}
gTypeRequestInit :: JSM GType
gTypeRequestInit = GType . Object <$> jsg "RequestInit"
newtype Response = Response { unResponse :: JSVal }
instance PToJSVal Response where
pToJSVal = unResponse
{-# INLINE pToJSVal #-}
instance PFromJSVal Response where
pFromJSVal = Response
{-# INLINE pFromJSVal #-}
instance ToJSVal Response where
toJSVal = return . unResponse
{-# INLINE toJSVal #-}
instance FromJSVal Response where
fromJSVal v = fmap Response <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Response
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Response where
makeObject = makeObject . unResponse
instance IsGObject Response where
typeGType _ = gTypeResponse
{-# INLINE typeGType #-}
noResponse :: Maybe Response
noResponse = Nothing
{-# INLINE noResponse #-}
gTypeResponse :: JSM GType
gTypeResponse = GType . Object <$> jsg "Response"
newtype RotationRate = RotationRate { unRotationRate :: JSVal }
instance PToJSVal RotationRate where
pToJSVal = unRotationRate
{-# INLINE pToJSVal #-}
instance PFromJSVal RotationRate where
pFromJSVal = RotationRate
{-# INLINE pFromJSVal #-}
instance ToJSVal RotationRate where
toJSVal = return . unRotationRate
{-# INLINE toJSVal #-}
instance FromJSVal RotationRate where
fromJSVal v = fmap RotationRate <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RotationRate
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RotationRate where
makeObject = makeObject . unRotationRate
instance IsGObject RotationRate where
typeGType _ = gTypeRotationRate
{-# INLINE typeGType #-}
noRotationRate :: Maybe RotationRate
noRotationRate = Nothing
{-# INLINE noRotationRate #-}
gTypeRotationRate :: JSM GType
gTypeRotationRate = GType . Object <$> jsg "RotationRate"
newtype RsaHashedImportParams = RsaHashedImportParams { unRsaHashedImportParams :: JSVal }
instance PToJSVal RsaHashedImportParams where
pToJSVal = unRsaHashedImportParams
{-# INLINE pToJSVal #-}
instance PFromJSVal RsaHashedImportParams where
pFromJSVal = RsaHashedImportParams
{-# INLINE pFromJSVal #-}
instance ToJSVal RsaHashedImportParams where
toJSVal = return . unRsaHashedImportParams
{-# INLINE toJSVal #-}
instance FromJSVal RsaHashedImportParams where
fromJSVal v = fmap RsaHashedImportParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RsaHashedImportParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RsaHashedImportParams where
makeObject = makeObject . unRsaHashedImportParams
instance IsCryptoAlgorithmParameters RsaHashedImportParams
instance IsGObject RsaHashedImportParams where
typeGType _ = gTypeRsaHashedImportParams
{-# INLINE typeGType #-}
noRsaHashedImportParams :: Maybe RsaHashedImportParams
noRsaHashedImportParams = Nothing
{-# INLINE noRsaHashedImportParams #-}
gTypeRsaHashedImportParams :: JSM GType
gTypeRsaHashedImportParams = GType . Object <$> jsg "RsaHashedImportParams"
newtype RsaHashedKeyGenParams = RsaHashedKeyGenParams { unRsaHashedKeyGenParams :: JSVal }
instance PToJSVal RsaHashedKeyGenParams where
pToJSVal = unRsaHashedKeyGenParams
{-# INLINE pToJSVal #-}
instance PFromJSVal RsaHashedKeyGenParams where
pFromJSVal = RsaHashedKeyGenParams
{-# INLINE pFromJSVal #-}
instance ToJSVal RsaHashedKeyGenParams where
toJSVal = return . unRsaHashedKeyGenParams
{-# INLINE toJSVal #-}
instance FromJSVal RsaHashedKeyGenParams where
fromJSVal v = fmap RsaHashedKeyGenParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RsaHashedKeyGenParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RsaHashedKeyGenParams where
makeObject = makeObject . unRsaHashedKeyGenParams
instance IsRsaKeyGenParams RsaHashedKeyGenParams
instance IsCryptoAlgorithmParameters RsaHashedKeyGenParams
instance IsGObject RsaHashedKeyGenParams where
typeGType _ = gTypeRsaHashedKeyGenParams
{-# INLINE typeGType #-}
noRsaHashedKeyGenParams :: Maybe RsaHashedKeyGenParams
noRsaHashedKeyGenParams = Nothing
{-# INLINE noRsaHashedKeyGenParams #-}
gTypeRsaHashedKeyGenParams :: JSM GType
gTypeRsaHashedKeyGenParams = GType . Object <$> jsg "RsaHashedKeyGenParams"
newtype RsaKeyGenParams = RsaKeyGenParams { unRsaKeyGenParams :: JSVal }
instance PToJSVal RsaKeyGenParams where
pToJSVal = unRsaKeyGenParams
{-# INLINE pToJSVal #-}
instance PFromJSVal RsaKeyGenParams where
pFromJSVal = RsaKeyGenParams
{-# INLINE pFromJSVal #-}
instance ToJSVal RsaKeyGenParams where
toJSVal = return . unRsaKeyGenParams
{-# INLINE toJSVal #-}
instance FromJSVal RsaKeyGenParams where
fromJSVal v = fmap RsaKeyGenParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RsaKeyGenParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RsaKeyGenParams where
makeObject = makeObject . unRsaKeyGenParams
class (IsCryptoAlgorithmParameters o, IsGObject o) => IsRsaKeyGenParams o
toRsaKeyGenParams :: IsRsaKeyGenParams o => o -> RsaKeyGenParams
toRsaKeyGenParams = RsaKeyGenParams . coerce
instance IsRsaKeyGenParams RsaKeyGenParams
instance IsCryptoAlgorithmParameters RsaKeyGenParams
instance IsGObject RsaKeyGenParams where
typeGType _ = gTypeRsaKeyGenParams
{-# INLINE typeGType #-}
noRsaKeyGenParams :: Maybe RsaKeyGenParams
noRsaKeyGenParams = Nothing
{-# INLINE noRsaKeyGenParams #-}
gTypeRsaKeyGenParams :: JSM GType
gTypeRsaKeyGenParams = GType . Object <$> jsg "RsaKeyGenParams"
newtype RsaOaepParams = RsaOaepParams { unRsaOaepParams :: JSVal }
instance PToJSVal RsaOaepParams where
pToJSVal = unRsaOaepParams
{-# INLINE pToJSVal #-}
instance PFromJSVal RsaOaepParams where
pFromJSVal = RsaOaepParams
{-# INLINE pFromJSVal #-}
instance ToJSVal RsaOaepParams where
toJSVal = return . unRsaOaepParams
{-# INLINE toJSVal #-}
instance FromJSVal RsaOaepParams where
fromJSVal v = fmap RsaOaepParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RsaOaepParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RsaOaepParams where
makeObject = makeObject . unRsaOaepParams
instance IsCryptoAlgorithmParameters RsaOaepParams
instance IsGObject RsaOaepParams where
typeGType _ = gTypeRsaOaepParams
{-# INLINE typeGType #-}
noRsaOaepParams :: Maybe RsaOaepParams
noRsaOaepParams = Nothing
{-# INLINE noRsaOaepParams #-}
gTypeRsaOaepParams :: JSM GType
gTypeRsaOaepParams = GType . Object <$> jsg "RsaOaepParams"
newtype RsaOtherPrimesInfo = RsaOtherPrimesInfo { unRsaOtherPrimesInfo :: JSVal }
instance PToJSVal RsaOtherPrimesInfo where
pToJSVal = unRsaOtherPrimesInfo
{-# INLINE pToJSVal #-}
instance PFromJSVal RsaOtherPrimesInfo where
pFromJSVal = RsaOtherPrimesInfo
{-# INLINE pFromJSVal #-}
instance ToJSVal RsaOtherPrimesInfo where
toJSVal = return . unRsaOtherPrimesInfo
{-# INLINE toJSVal #-}
instance FromJSVal RsaOtherPrimesInfo where
fromJSVal v = fmap RsaOtherPrimesInfo <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . RsaOtherPrimesInfo
{-# INLINE fromJSValUnchecked #-}
instance MakeObject RsaOtherPrimesInfo where
makeObject = makeObject . unRsaOtherPrimesInfo
instance IsGObject RsaOtherPrimesInfo where
typeGType _ = gTypeRsaOtherPrimesInfo
{-# INLINE typeGType #-}
noRsaOtherPrimesInfo :: Maybe RsaOtherPrimesInfo
noRsaOtherPrimesInfo = Nothing
{-# INLINE noRsaOtherPrimesInfo #-}
gTypeRsaOtherPrimesInfo :: JSM GType
gTypeRsaOtherPrimesInfo = GType . Object <$> jsg "RsaOtherPrimesInfo"
newtype SQLError = SQLError { unSQLError :: JSVal }
instance PToJSVal SQLError where
pToJSVal = unSQLError
{-# INLINE pToJSVal #-}
instance PFromJSVal SQLError where
pFromJSVal = SQLError
{-# INLINE pFromJSVal #-}
instance ToJSVal SQLError where
toJSVal = return . unSQLError
{-# INLINE toJSVal #-}
instance FromJSVal SQLError where
fromJSVal v = fmap SQLError <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SQLError
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SQLError where
makeObject = makeObject . unSQLError
instance IsGObject SQLError where
typeGType _ = gTypeSQLError
{-# INLINE typeGType #-}
noSQLError :: Maybe SQLError
noSQLError = Nothing
{-# INLINE noSQLError #-}
gTypeSQLError :: JSM GType
gTypeSQLError = GType . Object <$> jsg "SQLError"
newtype SQLException = SQLException { unSQLException :: JSVal }
instance PToJSVal SQLException where
pToJSVal = unSQLException
{-# INLINE pToJSVal #-}
instance PFromJSVal SQLException where
pFromJSVal = SQLException
{-# INLINE pFromJSVal #-}
instance ToJSVal SQLException where
toJSVal = return . unSQLException
{-# INLINE toJSVal #-}
instance FromJSVal SQLException where
fromJSVal v = fmap SQLException <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SQLException
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SQLException where
makeObject = makeObject . unSQLException
instance IsGObject SQLException where
typeGType _ = gTypeSQLException
{-# INLINE typeGType #-}
noSQLException :: Maybe SQLException
noSQLException = Nothing
{-# INLINE noSQLException #-}
gTypeSQLException :: JSM GType
gTypeSQLException = GType . Object <$> jsg "SQLException"
newtype SQLResultSet = SQLResultSet { unSQLResultSet :: JSVal }
instance PToJSVal SQLResultSet where
pToJSVal = unSQLResultSet
{-# INLINE pToJSVal #-}
instance PFromJSVal SQLResultSet where
pFromJSVal = SQLResultSet
{-# INLINE pFromJSVal #-}
instance ToJSVal SQLResultSet where
toJSVal = return . unSQLResultSet
{-# INLINE toJSVal #-}
instance FromJSVal SQLResultSet where
fromJSVal v = fmap SQLResultSet <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SQLResultSet
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SQLResultSet where
makeObject = makeObject . unSQLResultSet
instance IsGObject SQLResultSet where
typeGType _ = gTypeSQLResultSet
{-# INLINE typeGType #-}
noSQLResultSet :: Maybe SQLResultSet
noSQLResultSet = Nothing
{-# INLINE noSQLResultSet #-}
gTypeSQLResultSet :: JSM GType
gTypeSQLResultSet = GType . Object <$> jsg "SQLResultSet"
newtype SQLResultSetRowList = SQLResultSetRowList { unSQLResultSetRowList :: JSVal }
instance PToJSVal SQLResultSetRowList where
pToJSVal = unSQLResultSetRowList
{-# INLINE pToJSVal #-}
instance PFromJSVal SQLResultSetRowList where
pFromJSVal = SQLResultSetRowList
{-# INLINE pFromJSVal #-}
instance ToJSVal SQLResultSetRowList where
toJSVal = return . unSQLResultSetRowList
{-# INLINE toJSVal #-}
instance FromJSVal SQLResultSetRowList where
fromJSVal v = fmap SQLResultSetRowList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SQLResultSetRowList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SQLResultSetRowList where
makeObject = makeObject . unSQLResultSetRowList
instance IsGObject SQLResultSetRowList where
typeGType _ = gTypeSQLResultSetRowList
{-# INLINE typeGType #-}
noSQLResultSetRowList :: Maybe SQLResultSetRowList
noSQLResultSetRowList = Nothing
{-# INLINE noSQLResultSetRowList #-}
gTypeSQLResultSetRowList :: JSM GType
gTypeSQLResultSetRowList = GType . Object <$> jsg "SQLResultSetRowList"
newtype SQLTransaction = SQLTransaction { unSQLTransaction :: JSVal }
instance PToJSVal SQLTransaction where
pToJSVal = unSQLTransaction
{-# INLINE pToJSVal #-}
instance PFromJSVal SQLTransaction where
pFromJSVal = SQLTransaction
{-# INLINE pFromJSVal #-}
instance ToJSVal SQLTransaction where
toJSVal = return . unSQLTransaction
{-# INLINE toJSVal #-}
instance FromJSVal SQLTransaction where
fromJSVal v = fmap SQLTransaction <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SQLTransaction
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SQLTransaction where
makeObject = makeObject . unSQLTransaction
instance IsGObject SQLTransaction where
typeGType _ = gTypeSQLTransaction
{-# INLINE typeGType #-}
noSQLTransaction :: Maybe SQLTransaction
noSQLTransaction = Nothing
{-# INLINE noSQLTransaction #-}
gTypeSQLTransaction :: JSM GType
gTypeSQLTransaction = GType . Object <$> jsg "SQLTransaction"
newtype SVGAElement = SVGAElement { unSVGAElement :: JSVal }
instance PToJSVal SVGAElement where
pToJSVal = unSVGAElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAElement where
pFromJSVal = SVGAElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAElement where
toJSVal = return . unSVGAElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGAElement where
fromJSVal v = fmap SVGAElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAElement where
makeObject = makeObject . unSVGAElement
instance IsSVGGraphicsElement SVGAElement
instance IsSVGElement SVGAElement
instance IsElement SVGAElement
instance IsNode SVGAElement
instance IsEventTarget SVGAElement
instance IsSlotable SVGAElement
instance IsParentNode SVGAElement
instance IsNonDocumentTypeChildNode SVGAElement
instance IsDocumentAndElementEventHandlers SVGAElement
instance IsChildNode SVGAElement
instance IsAnimatable SVGAElement
instance IsGlobalEventHandlers SVGAElement
instance IsElementCSSInlineStyle SVGAElement
instance IsSVGTests SVGAElement
instance IsSVGURIReference SVGAElement
instance IsSVGExternalResourcesRequired SVGAElement
instance IsGObject SVGAElement where
typeGType _ = gTypeSVGAElement
{-# INLINE typeGType #-}
noSVGAElement :: Maybe SVGAElement
noSVGAElement = Nothing
{-# INLINE noSVGAElement #-}
gTypeSVGAElement :: JSM GType
gTypeSVGAElement = GType . Object <$> jsg "SVGAElement"
newtype SVGAltGlyphDefElement = SVGAltGlyphDefElement { unSVGAltGlyphDefElement :: JSVal }
instance PToJSVal SVGAltGlyphDefElement where
pToJSVal = unSVGAltGlyphDefElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAltGlyphDefElement where
pFromJSVal = SVGAltGlyphDefElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAltGlyphDefElement where
toJSVal = return . unSVGAltGlyphDefElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGAltGlyphDefElement where
fromJSVal v = fmap SVGAltGlyphDefElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAltGlyphDefElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAltGlyphDefElement where
makeObject = makeObject . unSVGAltGlyphDefElement
instance IsSVGElement SVGAltGlyphDefElement
instance IsElement SVGAltGlyphDefElement
instance IsNode SVGAltGlyphDefElement
instance IsEventTarget SVGAltGlyphDefElement
instance IsSlotable SVGAltGlyphDefElement
instance IsParentNode SVGAltGlyphDefElement
instance IsNonDocumentTypeChildNode SVGAltGlyphDefElement
instance IsDocumentAndElementEventHandlers SVGAltGlyphDefElement
instance IsChildNode SVGAltGlyphDefElement
instance IsAnimatable SVGAltGlyphDefElement
instance IsGlobalEventHandlers SVGAltGlyphDefElement
instance IsElementCSSInlineStyle SVGAltGlyphDefElement
instance IsGObject SVGAltGlyphDefElement where
typeGType _ = gTypeSVGAltGlyphDefElement
{-# INLINE typeGType #-}
noSVGAltGlyphDefElement :: Maybe SVGAltGlyphDefElement
noSVGAltGlyphDefElement = Nothing
{-# INLINE noSVGAltGlyphDefElement #-}
gTypeSVGAltGlyphDefElement :: JSM GType
gTypeSVGAltGlyphDefElement = GType . Object <$> jsg "SVGAltGlyphDefElement"
newtype SVGAltGlyphElement = SVGAltGlyphElement { unSVGAltGlyphElement :: JSVal }
instance PToJSVal SVGAltGlyphElement where
pToJSVal = unSVGAltGlyphElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAltGlyphElement where
pFromJSVal = SVGAltGlyphElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAltGlyphElement where
toJSVal = return . unSVGAltGlyphElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGAltGlyphElement where
fromJSVal v = fmap SVGAltGlyphElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAltGlyphElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAltGlyphElement where
makeObject = makeObject . unSVGAltGlyphElement
instance IsSVGTextPositioningElement SVGAltGlyphElement
instance IsSVGTextContentElement SVGAltGlyphElement
instance IsSVGGraphicsElement SVGAltGlyphElement
instance IsSVGElement SVGAltGlyphElement
instance IsElement SVGAltGlyphElement
instance IsNode SVGAltGlyphElement
instance IsEventTarget SVGAltGlyphElement
instance IsSlotable SVGAltGlyphElement
instance IsParentNode SVGAltGlyphElement
instance IsNonDocumentTypeChildNode SVGAltGlyphElement
instance IsDocumentAndElementEventHandlers SVGAltGlyphElement
instance IsChildNode SVGAltGlyphElement
instance IsAnimatable SVGAltGlyphElement
instance IsGlobalEventHandlers SVGAltGlyphElement
instance IsElementCSSInlineStyle SVGAltGlyphElement
instance IsSVGTests SVGAltGlyphElement
instance IsSVGExternalResourcesRequired SVGAltGlyphElement
instance IsSVGURIReference SVGAltGlyphElement
instance IsGObject SVGAltGlyphElement where
typeGType _ = gTypeSVGAltGlyphElement
{-# INLINE typeGType #-}
noSVGAltGlyphElement :: Maybe SVGAltGlyphElement
noSVGAltGlyphElement = Nothing
{-# INLINE noSVGAltGlyphElement #-}
gTypeSVGAltGlyphElement :: JSM GType
gTypeSVGAltGlyphElement = GType . Object <$> jsg "SVGAltGlyphElement"
newtype SVGAltGlyphItemElement = SVGAltGlyphItemElement { unSVGAltGlyphItemElement :: JSVal }
instance PToJSVal SVGAltGlyphItemElement where
pToJSVal = unSVGAltGlyphItemElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAltGlyphItemElement where
pFromJSVal = SVGAltGlyphItemElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAltGlyphItemElement where
toJSVal = return . unSVGAltGlyphItemElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGAltGlyphItemElement where
fromJSVal v = fmap SVGAltGlyphItemElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAltGlyphItemElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAltGlyphItemElement where
makeObject = makeObject . unSVGAltGlyphItemElement
instance IsSVGElement SVGAltGlyphItemElement
instance IsElement SVGAltGlyphItemElement
instance IsNode SVGAltGlyphItemElement
instance IsEventTarget SVGAltGlyphItemElement
instance IsSlotable SVGAltGlyphItemElement
instance IsParentNode SVGAltGlyphItemElement
instance IsNonDocumentTypeChildNode SVGAltGlyphItemElement
instance IsDocumentAndElementEventHandlers SVGAltGlyphItemElement
instance IsChildNode SVGAltGlyphItemElement
instance IsAnimatable SVGAltGlyphItemElement
instance IsGlobalEventHandlers SVGAltGlyphItemElement
instance IsElementCSSInlineStyle SVGAltGlyphItemElement
instance IsGObject SVGAltGlyphItemElement where
typeGType _ = gTypeSVGAltGlyphItemElement
{-# INLINE typeGType #-}
noSVGAltGlyphItemElement :: Maybe SVGAltGlyphItemElement
noSVGAltGlyphItemElement = Nothing
{-# INLINE noSVGAltGlyphItemElement #-}
gTypeSVGAltGlyphItemElement :: JSM GType
gTypeSVGAltGlyphItemElement = GType . Object <$> jsg "SVGAltGlyphItemElement"
newtype SVGAngle = SVGAngle { unSVGAngle :: JSVal }
instance PToJSVal SVGAngle where
pToJSVal = unSVGAngle
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAngle where
pFromJSVal = SVGAngle
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAngle where
toJSVal = return . unSVGAngle
{-# INLINE toJSVal #-}
instance FromJSVal SVGAngle where
fromJSVal v = fmap SVGAngle <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAngle
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAngle where
makeObject = makeObject . unSVGAngle
instance IsGObject SVGAngle where
typeGType _ = gTypeSVGAngle
{-# INLINE typeGType #-}
noSVGAngle :: Maybe SVGAngle
noSVGAngle = Nothing
{-# INLINE noSVGAngle #-}
gTypeSVGAngle :: JSM GType
gTypeSVGAngle = GType . Object <$> jsg "SVGAngle"
newtype SVGAnimateColorElement = SVGAnimateColorElement { unSVGAnimateColorElement :: JSVal }
instance PToJSVal SVGAnimateColorElement where
pToJSVal = unSVGAnimateColorElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimateColorElement where
pFromJSVal = SVGAnimateColorElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimateColorElement where
toJSVal = return . unSVGAnimateColorElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimateColorElement where
fromJSVal v = fmap SVGAnimateColorElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimateColorElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimateColorElement where
makeObject = makeObject . unSVGAnimateColorElement
instance IsSVGAnimationElement SVGAnimateColorElement
instance IsSVGElement SVGAnimateColorElement
instance IsElement SVGAnimateColorElement
instance IsNode SVGAnimateColorElement
instance IsEventTarget SVGAnimateColorElement
instance IsSlotable SVGAnimateColorElement
instance IsParentNode SVGAnimateColorElement
instance IsNonDocumentTypeChildNode SVGAnimateColorElement
instance IsDocumentAndElementEventHandlers SVGAnimateColorElement
instance IsChildNode SVGAnimateColorElement
instance IsAnimatable SVGAnimateColorElement
instance IsGlobalEventHandlers SVGAnimateColorElement
instance IsElementCSSInlineStyle SVGAnimateColorElement
instance IsSVGTests SVGAnimateColorElement
instance IsSVGExternalResourcesRequired SVGAnimateColorElement
instance IsGObject SVGAnimateColorElement where
typeGType _ = gTypeSVGAnimateColorElement
{-# INLINE typeGType #-}
noSVGAnimateColorElement :: Maybe SVGAnimateColorElement
noSVGAnimateColorElement = Nothing
{-# INLINE noSVGAnimateColorElement #-}
gTypeSVGAnimateColorElement :: JSM GType
gTypeSVGAnimateColorElement = GType . Object <$> jsg "SVGAnimateColorElement"
newtype SVGAnimateElement = SVGAnimateElement { unSVGAnimateElement :: JSVal }
instance PToJSVal SVGAnimateElement where
pToJSVal = unSVGAnimateElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimateElement where
pFromJSVal = SVGAnimateElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimateElement where
toJSVal = return . unSVGAnimateElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimateElement where
fromJSVal v = fmap SVGAnimateElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimateElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimateElement where
makeObject = makeObject . unSVGAnimateElement
instance IsSVGAnimationElement SVGAnimateElement
instance IsSVGElement SVGAnimateElement
instance IsElement SVGAnimateElement
instance IsNode SVGAnimateElement
instance IsEventTarget SVGAnimateElement
instance IsSlotable SVGAnimateElement
instance IsParentNode SVGAnimateElement
instance IsNonDocumentTypeChildNode SVGAnimateElement
instance IsDocumentAndElementEventHandlers SVGAnimateElement
instance IsChildNode SVGAnimateElement
instance IsAnimatable SVGAnimateElement
instance IsGlobalEventHandlers SVGAnimateElement
instance IsElementCSSInlineStyle SVGAnimateElement
instance IsSVGTests SVGAnimateElement
instance IsSVGExternalResourcesRequired SVGAnimateElement
instance IsGObject SVGAnimateElement where
typeGType _ = gTypeSVGAnimateElement
{-# INLINE typeGType #-}
noSVGAnimateElement :: Maybe SVGAnimateElement
noSVGAnimateElement = Nothing
{-# INLINE noSVGAnimateElement #-}
gTypeSVGAnimateElement :: JSM GType
gTypeSVGAnimateElement = GType . Object <$> jsg "SVGAnimateElement"
newtype SVGAnimateMotionElement = SVGAnimateMotionElement { unSVGAnimateMotionElement :: JSVal }
instance PToJSVal SVGAnimateMotionElement where
pToJSVal = unSVGAnimateMotionElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimateMotionElement where
pFromJSVal = SVGAnimateMotionElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimateMotionElement where
toJSVal = return . unSVGAnimateMotionElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimateMotionElement where
fromJSVal v = fmap SVGAnimateMotionElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimateMotionElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimateMotionElement where
makeObject = makeObject . unSVGAnimateMotionElement
instance IsSVGAnimationElement SVGAnimateMotionElement
instance IsSVGElement SVGAnimateMotionElement
instance IsElement SVGAnimateMotionElement
instance IsNode SVGAnimateMotionElement
instance IsEventTarget SVGAnimateMotionElement
instance IsSlotable SVGAnimateMotionElement
instance IsParentNode SVGAnimateMotionElement
instance IsNonDocumentTypeChildNode SVGAnimateMotionElement
instance IsDocumentAndElementEventHandlers SVGAnimateMotionElement
instance IsChildNode SVGAnimateMotionElement
instance IsAnimatable SVGAnimateMotionElement
instance IsGlobalEventHandlers SVGAnimateMotionElement
instance IsElementCSSInlineStyle SVGAnimateMotionElement
instance IsSVGTests SVGAnimateMotionElement
instance IsSVGExternalResourcesRequired SVGAnimateMotionElement
instance IsGObject SVGAnimateMotionElement where
typeGType _ = gTypeSVGAnimateMotionElement
{-# INLINE typeGType #-}
noSVGAnimateMotionElement :: Maybe SVGAnimateMotionElement
noSVGAnimateMotionElement = Nothing
{-# INLINE noSVGAnimateMotionElement #-}
gTypeSVGAnimateMotionElement :: JSM GType
gTypeSVGAnimateMotionElement = GType . Object <$> jsg "SVGAnimateMotionElement"
newtype SVGAnimateTransformElement = SVGAnimateTransformElement { unSVGAnimateTransformElement :: JSVal }
instance PToJSVal SVGAnimateTransformElement where
pToJSVal = unSVGAnimateTransformElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimateTransformElement where
pFromJSVal = SVGAnimateTransformElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimateTransformElement where
toJSVal = return . unSVGAnimateTransformElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimateTransformElement where
fromJSVal v = fmap SVGAnimateTransformElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimateTransformElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimateTransformElement where
makeObject = makeObject . unSVGAnimateTransformElement
instance IsSVGAnimationElement SVGAnimateTransformElement
instance IsSVGElement SVGAnimateTransformElement
instance IsElement SVGAnimateTransformElement
instance IsNode SVGAnimateTransformElement
instance IsEventTarget SVGAnimateTransformElement
instance IsSlotable SVGAnimateTransformElement
instance IsParentNode SVGAnimateTransformElement
instance IsNonDocumentTypeChildNode SVGAnimateTransformElement
instance IsDocumentAndElementEventHandlers SVGAnimateTransformElement
instance IsChildNode SVGAnimateTransformElement
instance IsAnimatable SVGAnimateTransformElement
instance IsGlobalEventHandlers SVGAnimateTransformElement
instance IsElementCSSInlineStyle SVGAnimateTransformElement
instance IsSVGTests SVGAnimateTransformElement
instance IsSVGExternalResourcesRequired SVGAnimateTransformElement
instance IsGObject SVGAnimateTransformElement where
typeGType _ = gTypeSVGAnimateTransformElement
{-# INLINE typeGType #-}
noSVGAnimateTransformElement :: Maybe SVGAnimateTransformElement
noSVGAnimateTransformElement = Nothing
{-# INLINE noSVGAnimateTransformElement #-}
gTypeSVGAnimateTransformElement :: JSM GType
gTypeSVGAnimateTransformElement = GType . Object <$> jsg "SVGAnimateTransformElement"
newtype SVGAnimatedAngle = SVGAnimatedAngle { unSVGAnimatedAngle :: JSVal }
instance PToJSVal SVGAnimatedAngle where
pToJSVal = unSVGAnimatedAngle
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedAngle where
pFromJSVal = SVGAnimatedAngle
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedAngle where
toJSVal = return . unSVGAnimatedAngle
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedAngle where
fromJSVal v = fmap SVGAnimatedAngle <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedAngle
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedAngle where
makeObject = makeObject . unSVGAnimatedAngle
instance IsGObject SVGAnimatedAngle where
typeGType _ = gTypeSVGAnimatedAngle
{-# INLINE typeGType #-}
noSVGAnimatedAngle :: Maybe SVGAnimatedAngle
noSVGAnimatedAngle = Nothing
{-# INLINE noSVGAnimatedAngle #-}
gTypeSVGAnimatedAngle :: JSM GType
gTypeSVGAnimatedAngle = GType . Object <$> jsg "SVGAnimatedAngle"
newtype SVGAnimatedBoolean = SVGAnimatedBoolean { unSVGAnimatedBoolean :: JSVal }
instance PToJSVal SVGAnimatedBoolean where
pToJSVal = unSVGAnimatedBoolean
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedBoolean where
pFromJSVal = SVGAnimatedBoolean
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedBoolean where
toJSVal = return . unSVGAnimatedBoolean
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedBoolean where
fromJSVal v = fmap SVGAnimatedBoolean <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedBoolean
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedBoolean where
makeObject = makeObject . unSVGAnimatedBoolean
instance IsGObject SVGAnimatedBoolean where
typeGType _ = gTypeSVGAnimatedBoolean
{-# INLINE typeGType #-}
noSVGAnimatedBoolean :: Maybe SVGAnimatedBoolean
noSVGAnimatedBoolean = Nothing
{-# INLINE noSVGAnimatedBoolean #-}
gTypeSVGAnimatedBoolean :: JSM GType
gTypeSVGAnimatedBoolean = GType . Object <$> jsg "SVGAnimatedBoolean"
newtype SVGAnimatedEnumeration = SVGAnimatedEnumeration { unSVGAnimatedEnumeration :: JSVal }
instance PToJSVal SVGAnimatedEnumeration where
pToJSVal = unSVGAnimatedEnumeration
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedEnumeration where
pFromJSVal = SVGAnimatedEnumeration
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedEnumeration where
toJSVal = return . unSVGAnimatedEnumeration
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedEnumeration where
fromJSVal v = fmap SVGAnimatedEnumeration <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedEnumeration
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedEnumeration where
makeObject = makeObject . unSVGAnimatedEnumeration
instance IsGObject SVGAnimatedEnumeration where
typeGType _ = gTypeSVGAnimatedEnumeration
{-# INLINE typeGType #-}
noSVGAnimatedEnumeration :: Maybe SVGAnimatedEnumeration
noSVGAnimatedEnumeration = Nothing
{-# INLINE noSVGAnimatedEnumeration #-}
gTypeSVGAnimatedEnumeration :: JSM GType
gTypeSVGAnimatedEnumeration = GType . Object <$> jsg "SVGAnimatedEnumeration"
newtype SVGAnimatedInteger = SVGAnimatedInteger { unSVGAnimatedInteger :: JSVal }
instance PToJSVal SVGAnimatedInteger where
pToJSVal = unSVGAnimatedInteger
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedInteger where
pFromJSVal = SVGAnimatedInteger
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedInteger where
toJSVal = return . unSVGAnimatedInteger
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedInteger where
fromJSVal v = fmap SVGAnimatedInteger <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedInteger
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedInteger where
makeObject = makeObject . unSVGAnimatedInteger
instance IsGObject SVGAnimatedInteger where
typeGType _ = gTypeSVGAnimatedInteger
{-# INLINE typeGType #-}
noSVGAnimatedInteger :: Maybe SVGAnimatedInteger
noSVGAnimatedInteger = Nothing
{-# INLINE noSVGAnimatedInteger #-}
gTypeSVGAnimatedInteger :: JSM GType
gTypeSVGAnimatedInteger = GType . Object <$> jsg "SVGAnimatedInteger"
newtype SVGAnimatedLength = SVGAnimatedLength { unSVGAnimatedLength :: JSVal }
instance PToJSVal SVGAnimatedLength where
pToJSVal = unSVGAnimatedLength
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedLength where
pFromJSVal = SVGAnimatedLength
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedLength where
toJSVal = return . unSVGAnimatedLength
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedLength where
fromJSVal v = fmap SVGAnimatedLength <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedLength
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedLength where
makeObject = makeObject . unSVGAnimatedLength
instance IsGObject SVGAnimatedLength where
typeGType _ = gTypeSVGAnimatedLength
{-# INLINE typeGType #-}
noSVGAnimatedLength :: Maybe SVGAnimatedLength
noSVGAnimatedLength = Nothing
{-# INLINE noSVGAnimatedLength #-}
gTypeSVGAnimatedLength :: JSM GType
gTypeSVGAnimatedLength = GType . Object <$> jsg "SVGAnimatedLength"
newtype SVGAnimatedLengthList = SVGAnimatedLengthList { unSVGAnimatedLengthList :: JSVal }
instance PToJSVal SVGAnimatedLengthList where
pToJSVal = unSVGAnimatedLengthList
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedLengthList where
pFromJSVal = SVGAnimatedLengthList
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedLengthList where
toJSVal = return . unSVGAnimatedLengthList
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedLengthList where
fromJSVal v = fmap SVGAnimatedLengthList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedLengthList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedLengthList where
makeObject = makeObject . unSVGAnimatedLengthList
instance IsGObject SVGAnimatedLengthList where
typeGType _ = gTypeSVGAnimatedLengthList
{-# INLINE typeGType #-}
noSVGAnimatedLengthList :: Maybe SVGAnimatedLengthList
noSVGAnimatedLengthList = Nothing
{-# INLINE noSVGAnimatedLengthList #-}
gTypeSVGAnimatedLengthList :: JSM GType
gTypeSVGAnimatedLengthList = GType . Object <$> jsg "SVGAnimatedLengthList"
newtype SVGAnimatedNumber = SVGAnimatedNumber { unSVGAnimatedNumber :: JSVal }
instance PToJSVal SVGAnimatedNumber where
pToJSVal = unSVGAnimatedNumber
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedNumber where
pFromJSVal = SVGAnimatedNumber
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedNumber where
toJSVal = return . unSVGAnimatedNumber
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedNumber where
fromJSVal v = fmap SVGAnimatedNumber <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedNumber
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedNumber where
makeObject = makeObject . unSVGAnimatedNumber
instance IsGObject SVGAnimatedNumber where
typeGType _ = gTypeSVGAnimatedNumber
{-# INLINE typeGType #-}
noSVGAnimatedNumber :: Maybe SVGAnimatedNumber
noSVGAnimatedNumber = Nothing
{-# INLINE noSVGAnimatedNumber #-}
gTypeSVGAnimatedNumber :: JSM GType
gTypeSVGAnimatedNumber = GType . Object <$> jsg "SVGAnimatedNumber"
newtype SVGAnimatedNumberList = SVGAnimatedNumberList { unSVGAnimatedNumberList :: JSVal }
instance PToJSVal SVGAnimatedNumberList where
pToJSVal = unSVGAnimatedNumberList
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedNumberList where
pFromJSVal = SVGAnimatedNumberList
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedNumberList where
toJSVal = return . unSVGAnimatedNumberList
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedNumberList where
fromJSVal v = fmap SVGAnimatedNumberList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedNumberList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedNumberList where
makeObject = makeObject . unSVGAnimatedNumberList
instance IsGObject SVGAnimatedNumberList where
typeGType _ = gTypeSVGAnimatedNumberList
{-# INLINE typeGType #-}
noSVGAnimatedNumberList :: Maybe SVGAnimatedNumberList
noSVGAnimatedNumberList = Nothing
{-# INLINE noSVGAnimatedNumberList #-}
gTypeSVGAnimatedNumberList :: JSM GType
gTypeSVGAnimatedNumberList = GType . Object <$> jsg "SVGAnimatedNumberList"
newtype SVGAnimatedPreserveAspectRatio = SVGAnimatedPreserveAspectRatio { unSVGAnimatedPreserveAspectRatio :: JSVal }
instance PToJSVal SVGAnimatedPreserveAspectRatio where
pToJSVal = unSVGAnimatedPreserveAspectRatio
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedPreserveAspectRatio where
pFromJSVal = SVGAnimatedPreserveAspectRatio
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedPreserveAspectRatio where
toJSVal = return . unSVGAnimatedPreserveAspectRatio
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedPreserveAspectRatio where
fromJSVal v = fmap SVGAnimatedPreserveAspectRatio <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedPreserveAspectRatio
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedPreserveAspectRatio where
makeObject = makeObject . unSVGAnimatedPreserveAspectRatio
instance IsGObject SVGAnimatedPreserveAspectRatio where
typeGType _ = gTypeSVGAnimatedPreserveAspectRatio
{-# INLINE typeGType #-}
noSVGAnimatedPreserveAspectRatio :: Maybe SVGAnimatedPreserveAspectRatio
noSVGAnimatedPreserveAspectRatio = Nothing
{-# INLINE noSVGAnimatedPreserveAspectRatio #-}
gTypeSVGAnimatedPreserveAspectRatio :: JSM GType
gTypeSVGAnimatedPreserveAspectRatio = GType . Object <$> jsg "SVGAnimatedPreserveAspectRatio"
newtype SVGAnimatedRect = SVGAnimatedRect { unSVGAnimatedRect :: JSVal }
instance PToJSVal SVGAnimatedRect where
pToJSVal = unSVGAnimatedRect
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedRect where
pFromJSVal = SVGAnimatedRect
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedRect where
toJSVal = return . unSVGAnimatedRect
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedRect where
fromJSVal v = fmap SVGAnimatedRect <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedRect
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedRect where
makeObject = makeObject . unSVGAnimatedRect
instance IsGObject SVGAnimatedRect where
typeGType _ = gTypeSVGAnimatedRect
{-# INLINE typeGType #-}
noSVGAnimatedRect :: Maybe SVGAnimatedRect
noSVGAnimatedRect = Nothing
{-# INLINE noSVGAnimatedRect #-}
gTypeSVGAnimatedRect :: JSM GType
gTypeSVGAnimatedRect = GType . Object <$> jsg "SVGAnimatedRect"
newtype SVGAnimatedString = SVGAnimatedString { unSVGAnimatedString :: JSVal }
instance PToJSVal SVGAnimatedString where
pToJSVal = unSVGAnimatedString
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedString where
pFromJSVal = SVGAnimatedString
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedString where
toJSVal = return . unSVGAnimatedString
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedString where
fromJSVal v = fmap SVGAnimatedString <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedString
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedString where
makeObject = makeObject . unSVGAnimatedString
instance IsGObject SVGAnimatedString where
typeGType _ = gTypeSVGAnimatedString
{-# INLINE typeGType #-}
noSVGAnimatedString :: Maybe SVGAnimatedString
noSVGAnimatedString = Nothing
{-# INLINE noSVGAnimatedString #-}
gTypeSVGAnimatedString :: JSM GType
gTypeSVGAnimatedString = GType . Object <$> jsg "SVGAnimatedString"
newtype SVGAnimatedTransformList = SVGAnimatedTransformList { unSVGAnimatedTransformList :: JSVal }
instance PToJSVal SVGAnimatedTransformList where
pToJSVal = unSVGAnimatedTransformList
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimatedTransformList where
pFromJSVal = SVGAnimatedTransformList
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimatedTransformList where
toJSVal = return . unSVGAnimatedTransformList
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimatedTransformList where
fromJSVal v = fmap SVGAnimatedTransformList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimatedTransformList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimatedTransformList where
makeObject = makeObject . unSVGAnimatedTransformList
instance IsGObject SVGAnimatedTransformList where
typeGType _ = gTypeSVGAnimatedTransformList
{-# INLINE typeGType #-}
noSVGAnimatedTransformList :: Maybe SVGAnimatedTransformList
noSVGAnimatedTransformList = Nothing
{-# INLINE noSVGAnimatedTransformList #-}
gTypeSVGAnimatedTransformList :: JSM GType
gTypeSVGAnimatedTransformList = GType . Object <$> jsg "SVGAnimatedTransformList"
newtype SVGAnimationElement = SVGAnimationElement { unSVGAnimationElement :: JSVal }
instance PToJSVal SVGAnimationElement where
pToJSVal = unSVGAnimationElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGAnimationElement where
pFromJSVal = SVGAnimationElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGAnimationElement where
toJSVal = return . unSVGAnimationElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGAnimationElement where
fromJSVal v = fmap SVGAnimationElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGAnimationElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGAnimationElement where
makeObject = makeObject . unSVGAnimationElement
class (IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsSVGTests o, IsSVGExternalResourcesRequired o, IsGObject o) => IsSVGAnimationElement o
toSVGAnimationElement :: IsSVGAnimationElement o => o -> SVGAnimationElement
toSVGAnimationElement = SVGAnimationElement . coerce
instance IsSVGAnimationElement SVGAnimationElement
instance IsSVGElement SVGAnimationElement
instance IsElement SVGAnimationElement
instance IsNode SVGAnimationElement
instance IsEventTarget SVGAnimationElement
instance IsSlotable SVGAnimationElement
instance IsParentNode SVGAnimationElement
instance IsNonDocumentTypeChildNode SVGAnimationElement
instance IsDocumentAndElementEventHandlers SVGAnimationElement
instance IsChildNode SVGAnimationElement
instance IsAnimatable SVGAnimationElement
instance IsGlobalEventHandlers SVGAnimationElement
instance IsElementCSSInlineStyle SVGAnimationElement
instance IsSVGTests SVGAnimationElement
instance IsSVGExternalResourcesRequired SVGAnimationElement
instance IsGObject SVGAnimationElement where
typeGType _ = gTypeSVGAnimationElement
{-# INLINE typeGType #-}
noSVGAnimationElement :: Maybe SVGAnimationElement
noSVGAnimationElement = Nothing
{-# INLINE noSVGAnimationElement #-}
gTypeSVGAnimationElement :: JSM GType
gTypeSVGAnimationElement = GType . Object <$> jsg "SVGAnimationElement"
newtype SVGCircleElement = SVGCircleElement { unSVGCircleElement :: JSVal }
instance PToJSVal SVGCircleElement where
pToJSVal = unSVGCircleElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGCircleElement where
pFromJSVal = SVGCircleElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGCircleElement where
toJSVal = return . unSVGCircleElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGCircleElement where
fromJSVal v = fmap SVGCircleElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGCircleElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGCircleElement where
makeObject = makeObject . unSVGCircleElement
instance IsSVGGraphicsElement SVGCircleElement
instance IsSVGElement SVGCircleElement
instance IsElement SVGCircleElement
instance IsNode SVGCircleElement
instance IsEventTarget SVGCircleElement
instance IsSlotable SVGCircleElement
instance IsParentNode SVGCircleElement
instance IsNonDocumentTypeChildNode SVGCircleElement
instance IsDocumentAndElementEventHandlers SVGCircleElement
instance IsChildNode SVGCircleElement
instance IsAnimatable SVGCircleElement
instance IsGlobalEventHandlers SVGCircleElement
instance IsElementCSSInlineStyle SVGCircleElement
instance IsSVGTests SVGCircleElement
instance IsSVGExternalResourcesRequired SVGCircleElement
instance IsGObject SVGCircleElement where
typeGType _ = gTypeSVGCircleElement
{-# INLINE typeGType #-}
noSVGCircleElement :: Maybe SVGCircleElement
noSVGCircleElement = Nothing
{-# INLINE noSVGCircleElement #-}
gTypeSVGCircleElement :: JSM GType
gTypeSVGCircleElement = GType . Object <$> jsg "SVGCircleElement"
newtype SVGClipPathElement = SVGClipPathElement { unSVGClipPathElement :: JSVal }
instance PToJSVal SVGClipPathElement where
pToJSVal = unSVGClipPathElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGClipPathElement where
pFromJSVal = SVGClipPathElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGClipPathElement where
toJSVal = return . unSVGClipPathElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGClipPathElement where
fromJSVal v = fmap SVGClipPathElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGClipPathElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGClipPathElement where
makeObject = makeObject . unSVGClipPathElement
instance IsSVGGraphicsElement SVGClipPathElement
instance IsSVGElement SVGClipPathElement
instance IsElement SVGClipPathElement
instance IsNode SVGClipPathElement
instance IsEventTarget SVGClipPathElement
instance IsSlotable SVGClipPathElement
instance IsParentNode SVGClipPathElement
instance IsNonDocumentTypeChildNode SVGClipPathElement
instance IsDocumentAndElementEventHandlers SVGClipPathElement
instance IsChildNode SVGClipPathElement
instance IsAnimatable SVGClipPathElement
instance IsGlobalEventHandlers SVGClipPathElement
instance IsElementCSSInlineStyle SVGClipPathElement
instance IsSVGTests SVGClipPathElement
instance IsSVGExternalResourcesRequired SVGClipPathElement
instance IsGObject SVGClipPathElement where
typeGType _ = gTypeSVGClipPathElement
{-# INLINE typeGType #-}
noSVGClipPathElement :: Maybe SVGClipPathElement
noSVGClipPathElement = Nothing
{-# INLINE noSVGClipPathElement #-}
gTypeSVGClipPathElement :: JSM GType
gTypeSVGClipPathElement = GType . Object <$> jsg "SVGClipPathElement"
newtype SVGComponentTransferFunctionElement = SVGComponentTransferFunctionElement { unSVGComponentTransferFunctionElement :: JSVal }
instance PToJSVal SVGComponentTransferFunctionElement where
pToJSVal = unSVGComponentTransferFunctionElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGComponentTransferFunctionElement where
pFromJSVal = SVGComponentTransferFunctionElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGComponentTransferFunctionElement where
toJSVal = return . unSVGComponentTransferFunctionElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGComponentTransferFunctionElement where
fromJSVal v = fmap SVGComponentTransferFunctionElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGComponentTransferFunctionElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGComponentTransferFunctionElement where
makeObject = makeObject . unSVGComponentTransferFunctionElement
class (IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsGObject o) => IsSVGComponentTransferFunctionElement o
toSVGComponentTransferFunctionElement :: IsSVGComponentTransferFunctionElement o => o -> SVGComponentTransferFunctionElement
toSVGComponentTransferFunctionElement = SVGComponentTransferFunctionElement . coerce
instance IsSVGComponentTransferFunctionElement SVGComponentTransferFunctionElement
instance IsSVGElement SVGComponentTransferFunctionElement
instance IsElement SVGComponentTransferFunctionElement
instance IsNode SVGComponentTransferFunctionElement
instance IsEventTarget SVGComponentTransferFunctionElement
instance IsSlotable SVGComponentTransferFunctionElement
instance IsParentNode SVGComponentTransferFunctionElement
instance IsNonDocumentTypeChildNode SVGComponentTransferFunctionElement
instance IsDocumentAndElementEventHandlers SVGComponentTransferFunctionElement
instance IsChildNode SVGComponentTransferFunctionElement
instance IsAnimatable SVGComponentTransferFunctionElement
instance IsGlobalEventHandlers SVGComponentTransferFunctionElement
instance IsElementCSSInlineStyle SVGComponentTransferFunctionElement
instance IsGObject SVGComponentTransferFunctionElement where
typeGType _ = gTypeSVGComponentTransferFunctionElement
{-# INLINE typeGType #-}
noSVGComponentTransferFunctionElement :: Maybe SVGComponentTransferFunctionElement
noSVGComponentTransferFunctionElement = Nothing
{-# INLINE noSVGComponentTransferFunctionElement #-}
gTypeSVGComponentTransferFunctionElement :: JSM GType
gTypeSVGComponentTransferFunctionElement = GType . Object <$> jsg "SVGComponentTransferFunctionElement"
newtype SVGCursorElement = SVGCursorElement { unSVGCursorElement :: JSVal }
instance PToJSVal SVGCursorElement where
pToJSVal = unSVGCursorElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGCursorElement where
pFromJSVal = SVGCursorElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGCursorElement where
toJSVal = return . unSVGCursorElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGCursorElement where
fromJSVal v = fmap SVGCursorElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGCursorElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGCursorElement where
makeObject = makeObject . unSVGCursorElement
instance IsSVGElement SVGCursorElement
instance IsElement SVGCursorElement
instance IsNode SVGCursorElement
instance IsEventTarget SVGCursorElement
instance IsSlotable SVGCursorElement
instance IsParentNode SVGCursorElement
instance IsNonDocumentTypeChildNode SVGCursorElement
instance IsDocumentAndElementEventHandlers SVGCursorElement
instance IsChildNode SVGCursorElement
instance IsAnimatable SVGCursorElement
instance IsGlobalEventHandlers SVGCursorElement
instance IsElementCSSInlineStyle SVGCursorElement
instance IsSVGURIReference SVGCursorElement
instance IsSVGTests SVGCursorElement
instance IsSVGExternalResourcesRequired SVGCursorElement
instance IsGObject SVGCursorElement where
typeGType _ = gTypeSVGCursorElement
{-# INLINE typeGType #-}
noSVGCursorElement :: Maybe SVGCursorElement
noSVGCursorElement = Nothing
{-# INLINE noSVGCursorElement #-}
gTypeSVGCursorElement :: JSM GType
gTypeSVGCursorElement = GType . Object <$> jsg "SVGCursorElement"
newtype SVGDefsElement = SVGDefsElement { unSVGDefsElement :: JSVal }
instance PToJSVal SVGDefsElement where
pToJSVal = unSVGDefsElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGDefsElement where
pFromJSVal = SVGDefsElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGDefsElement where
toJSVal = return . unSVGDefsElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGDefsElement where
fromJSVal v = fmap SVGDefsElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGDefsElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGDefsElement where
makeObject = makeObject . unSVGDefsElement
instance IsSVGGraphicsElement SVGDefsElement
instance IsSVGElement SVGDefsElement
instance IsElement SVGDefsElement
instance IsNode SVGDefsElement
instance IsEventTarget SVGDefsElement
instance IsSlotable SVGDefsElement
instance IsParentNode SVGDefsElement
instance IsNonDocumentTypeChildNode SVGDefsElement
instance IsDocumentAndElementEventHandlers SVGDefsElement
instance IsChildNode SVGDefsElement
instance IsAnimatable SVGDefsElement
instance IsGlobalEventHandlers SVGDefsElement
instance IsElementCSSInlineStyle SVGDefsElement
instance IsSVGTests SVGDefsElement
instance IsSVGExternalResourcesRequired SVGDefsElement
instance IsGObject SVGDefsElement where
typeGType _ = gTypeSVGDefsElement
{-# INLINE typeGType #-}
noSVGDefsElement :: Maybe SVGDefsElement
noSVGDefsElement = Nothing
{-# INLINE noSVGDefsElement #-}
gTypeSVGDefsElement :: JSM GType
gTypeSVGDefsElement = GType . Object <$> jsg "SVGDefsElement"
newtype SVGDescElement = SVGDescElement { unSVGDescElement :: JSVal }
instance PToJSVal SVGDescElement where
pToJSVal = unSVGDescElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGDescElement where
pFromJSVal = SVGDescElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGDescElement where
toJSVal = return . unSVGDescElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGDescElement where
fromJSVal v = fmap SVGDescElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGDescElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGDescElement where
makeObject = makeObject . unSVGDescElement
instance IsSVGElement SVGDescElement
instance IsElement SVGDescElement
instance IsNode SVGDescElement
instance IsEventTarget SVGDescElement
instance IsSlotable SVGDescElement
instance IsParentNode SVGDescElement
instance IsNonDocumentTypeChildNode SVGDescElement
instance IsDocumentAndElementEventHandlers SVGDescElement
instance IsChildNode SVGDescElement
instance IsAnimatable SVGDescElement
instance IsGlobalEventHandlers SVGDescElement
instance IsElementCSSInlineStyle SVGDescElement
instance IsGObject SVGDescElement where
typeGType _ = gTypeSVGDescElement
{-# INLINE typeGType #-}
noSVGDescElement :: Maybe SVGDescElement
noSVGDescElement = Nothing
{-# INLINE noSVGDescElement #-}
gTypeSVGDescElement :: JSM GType
gTypeSVGDescElement = GType . Object <$> jsg "SVGDescElement"
newtype SVGElement = SVGElement { unSVGElement :: JSVal }
instance PToJSVal SVGElement where
pToJSVal = unSVGElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGElement where
pFromJSVal = SVGElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGElement where
toJSVal = return . unSVGElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGElement where
fromJSVal v = fmap SVGElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGElement where
makeObject = makeObject . unSVGElement
class (IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsGObject o) => IsSVGElement o
toSVGElement :: IsSVGElement o => o -> SVGElement
toSVGElement = SVGElement . coerce
instance IsSVGElement SVGElement
instance IsElement SVGElement
instance IsNode SVGElement
instance IsEventTarget SVGElement
instance IsSlotable SVGElement
instance IsParentNode SVGElement
instance IsNonDocumentTypeChildNode SVGElement
instance IsDocumentAndElementEventHandlers SVGElement
instance IsChildNode SVGElement
instance IsAnimatable SVGElement
instance IsGlobalEventHandlers SVGElement
instance IsElementCSSInlineStyle SVGElement
instance IsGObject SVGElement where
typeGType _ = gTypeSVGElement
{-# INLINE typeGType #-}
noSVGElement :: Maybe SVGElement
noSVGElement = Nothing
{-# INLINE noSVGElement #-}
gTypeSVGElement :: JSM GType
gTypeSVGElement = GType . Object <$> jsg "SVGElement"
newtype SVGEllipseElement = SVGEllipseElement { unSVGEllipseElement :: JSVal }
instance PToJSVal SVGEllipseElement where
pToJSVal = unSVGEllipseElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGEllipseElement where
pFromJSVal = SVGEllipseElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGEllipseElement where
toJSVal = return . unSVGEllipseElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGEllipseElement where
fromJSVal v = fmap SVGEllipseElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGEllipseElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGEllipseElement where
makeObject = makeObject . unSVGEllipseElement
instance IsSVGGraphicsElement SVGEllipseElement
instance IsSVGElement SVGEllipseElement
instance IsElement SVGEllipseElement
instance IsNode SVGEllipseElement
instance IsEventTarget SVGEllipseElement
instance IsSlotable SVGEllipseElement
instance IsParentNode SVGEllipseElement
instance IsNonDocumentTypeChildNode SVGEllipseElement
instance IsDocumentAndElementEventHandlers SVGEllipseElement
instance IsChildNode SVGEllipseElement
instance IsAnimatable SVGEllipseElement
instance IsGlobalEventHandlers SVGEllipseElement
instance IsElementCSSInlineStyle SVGEllipseElement
instance IsSVGTests SVGEllipseElement
instance IsSVGExternalResourcesRequired SVGEllipseElement
instance IsGObject SVGEllipseElement where
typeGType _ = gTypeSVGEllipseElement
{-# INLINE typeGType #-}
noSVGEllipseElement :: Maybe SVGEllipseElement
noSVGEllipseElement = Nothing
{-# INLINE noSVGEllipseElement #-}
gTypeSVGEllipseElement :: JSM GType
gTypeSVGEllipseElement = GType . Object <$> jsg "SVGEllipseElement"
newtype SVGException = SVGException { unSVGException :: JSVal }
instance PToJSVal SVGException where
pToJSVal = unSVGException
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGException where
pFromJSVal = SVGException
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGException where
toJSVal = return . unSVGException
{-# INLINE toJSVal #-}
instance FromJSVal SVGException where
fromJSVal v = fmap SVGException <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGException
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGException where
makeObject = makeObject . unSVGException
instance IsGObject SVGException where
typeGType _ = gTypeSVGException
{-# INLINE typeGType #-}
noSVGException :: Maybe SVGException
noSVGException = Nothing
{-# INLINE noSVGException #-}
gTypeSVGException :: JSM GType
gTypeSVGException = GType . Object <$> jsg "SVGException"
newtype SVGExternalResourcesRequired = SVGExternalResourcesRequired { unSVGExternalResourcesRequired :: JSVal }
instance PToJSVal SVGExternalResourcesRequired where
pToJSVal = unSVGExternalResourcesRequired
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGExternalResourcesRequired where
pFromJSVal = SVGExternalResourcesRequired
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGExternalResourcesRequired where
toJSVal = return . unSVGExternalResourcesRequired
{-# INLINE toJSVal #-}
instance FromJSVal SVGExternalResourcesRequired where
fromJSVal v = fmap SVGExternalResourcesRequired <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGExternalResourcesRequired
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGExternalResourcesRequired where
makeObject = makeObject . unSVGExternalResourcesRequired
class (IsGObject o) => IsSVGExternalResourcesRequired o
toSVGExternalResourcesRequired :: IsSVGExternalResourcesRequired o => o -> SVGExternalResourcesRequired
toSVGExternalResourcesRequired = SVGExternalResourcesRequired . coerce
instance IsSVGExternalResourcesRequired SVGExternalResourcesRequired
instance IsGObject SVGExternalResourcesRequired where
typeGType _ = gTypeSVGExternalResourcesRequired
{-# INLINE typeGType #-}
noSVGExternalResourcesRequired :: Maybe SVGExternalResourcesRequired
noSVGExternalResourcesRequired = Nothing
{-# INLINE noSVGExternalResourcesRequired #-}
gTypeSVGExternalResourcesRequired :: JSM GType
gTypeSVGExternalResourcesRequired = GType . Object <$> jsg "SVGExternalResourcesRequired"
newtype SVGFEBlendElement = SVGFEBlendElement { unSVGFEBlendElement :: JSVal }
instance PToJSVal SVGFEBlendElement where
pToJSVal = unSVGFEBlendElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEBlendElement where
pFromJSVal = SVGFEBlendElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEBlendElement where
toJSVal = return . unSVGFEBlendElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEBlendElement where
fromJSVal v = fmap SVGFEBlendElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEBlendElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEBlendElement where
makeObject = makeObject . unSVGFEBlendElement
instance IsSVGElement SVGFEBlendElement
instance IsElement SVGFEBlendElement
instance IsNode SVGFEBlendElement
instance IsEventTarget SVGFEBlendElement
instance IsSlotable SVGFEBlendElement
instance IsParentNode SVGFEBlendElement
instance IsNonDocumentTypeChildNode SVGFEBlendElement
instance IsDocumentAndElementEventHandlers SVGFEBlendElement
instance IsChildNode SVGFEBlendElement
instance IsAnimatable SVGFEBlendElement
instance IsGlobalEventHandlers SVGFEBlendElement
instance IsElementCSSInlineStyle SVGFEBlendElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEBlendElement
instance IsGObject SVGFEBlendElement where
typeGType _ = gTypeSVGFEBlendElement
{-# INLINE typeGType #-}
noSVGFEBlendElement :: Maybe SVGFEBlendElement
noSVGFEBlendElement = Nothing
{-# INLINE noSVGFEBlendElement #-}
gTypeSVGFEBlendElement :: JSM GType
gTypeSVGFEBlendElement = GType . Object <$> jsg "SVGFEBlendElement"
newtype SVGFEColorMatrixElement = SVGFEColorMatrixElement { unSVGFEColorMatrixElement :: JSVal }
instance PToJSVal SVGFEColorMatrixElement where
pToJSVal = unSVGFEColorMatrixElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEColorMatrixElement where
pFromJSVal = SVGFEColorMatrixElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEColorMatrixElement where
toJSVal = return . unSVGFEColorMatrixElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEColorMatrixElement where
fromJSVal v = fmap SVGFEColorMatrixElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEColorMatrixElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEColorMatrixElement where
makeObject = makeObject . unSVGFEColorMatrixElement
instance IsSVGElement SVGFEColorMatrixElement
instance IsElement SVGFEColorMatrixElement
instance IsNode SVGFEColorMatrixElement
instance IsEventTarget SVGFEColorMatrixElement
instance IsSlotable SVGFEColorMatrixElement
instance IsParentNode SVGFEColorMatrixElement
instance IsNonDocumentTypeChildNode SVGFEColorMatrixElement
instance IsDocumentAndElementEventHandlers SVGFEColorMatrixElement
instance IsChildNode SVGFEColorMatrixElement
instance IsAnimatable SVGFEColorMatrixElement
instance IsGlobalEventHandlers SVGFEColorMatrixElement
instance IsElementCSSInlineStyle SVGFEColorMatrixElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEColorMatrixElement
instance IsGObject SVGFEColorMatrixElement where
typeGType _ = gTypeSVGFEColorMatrixElement
{-# INLINE typeGType #-}
noSVGFEColorMatrixElement :: Maybe SVGFEColorMatrixElement
noSVGFEColorMatrixElement = Nothing
{-# INLINE noSVGFEColorMatrixElement #-}
gTypeSVGFEColorMatrixElement :: JSM GType
gTypeSVGFEColorMatrixElement = GType . Object <$> jsg "SVGFEColorMatrixElement"
newtype SVGFEComponentTransferElement = SVGFEComponentTransferElement { unSVGFEComponentTransferElement :: JSVal }
instance PToJSVal SVGFEComponentTransferElement where
pToJSVal = unSVGFEComponentTransferElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEComponentTransferElement where
pFromJSVal = SVGFEComponentTransferElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEComponentTransferElement where
toJSVal = return . unSVGFEComponentTransferElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEComponentTransferElement where
fromJSVal v = fmap SVGFEComponentTransferElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEComponentTransferElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEComponentTransferElement where
makeObject = makeObject . unSVGFEComponentTransferElement
instance IsSVGElement SVGFEComponentTransferElement
instance IsElement SVGFEComponentTransferElement
instance IsNode SVGFEComponentTransferElement
instance IsEventTarget SVGFEComponentTransferElement
instance IsSlotable SVGFEComponentTransferElement
instance IsParentNode SVGFEComponentTransferElement
instance IsNonDocumentTypeChildNode SVGFEComponentTransferElement
instance IsDocumentAndElementEventHandlers SVGFEComponentTransferElement
instance IsChildNode SVGFEComponentTransferElement
instance IsAnimatable SVGFEComponentTransferElement
instance IsGlobalEventHandlers SVGFEComponentTransferElement
instance IsElementCSSInlineStyle SVGFEComponentTransferElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEComponentTransferElement
instance IsGObject SVGFEComponentTransferElement where
typeGType _ = gTypeSVGFEComponentTransferElement
{-# INLINE typeGType #-}
noSVGFEComponentTransferElement :: Maybe SVGFEComponentTransferElement
noSVGFEComponentTransferElement = Nothing
{-# INLINE noSVGFEComponentTransferElement #-}
gTypeSVGFEComponentTransferElement :: JSM GType
gTypeSVGFEComponentTransferElement = GType . Object <$> jsg "SVGFEComponentTransferElement"
newtype SVGFECompositeElement = SVGFECompositeElement { unSVGFECompositeElement :: JSVal }
instance PToJSVal SVGFECompositeElement where
pToJSVal = unSVGFECompositeElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFECompositeElement where
pFromJSVal = SVGFECompositeElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFECompositeElement where
toJSVal = return . unSVGFECompositeElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFECompositeElement where
fromJSVal v = fmap SVGFECompositeElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFECompositeElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFECompositeElement where
makeObject = makeObject . unSVGFECompositeElement
instance IsSVGElement SVGFECompositeElement
instance IsElement SVGFECompositeElement
instance IsNode SVGFECompositeElement
instance IsEventTarget SVGFECompositeElement
instance IsSlotable SVGFECompositeElement
instance IsParentNode SVGFECompositeElement
instance IsNonDocumentTypeChildNode SVGFECompositeElement
instance IsDocumentAndElementEventHandlers SVGFECompositeElement
instance IsChildNode SVGFECompositeElement
instance IsAnimatable SVGFECompositeElement
instance IsGlobalEventHandlers SVGFECompositeElement
instance IsElementCSSInlineStyle SVGFECompositeElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFECompositeElement
instance IsGObject SVGFECompositeElement where
typeGType _ = gTypeSVGFECompositeElement
{-# INLINE typeGType #-}
noSVGFECompositeElement :: Maybe SVGFECompositeElement
noSVGFECompositeElement = Nothing
{-# INLINE noSVGFECompositeElement #-}
gTypeSVGFECompositeElement :: JSM GType
gTypeSVGFECompositeElement = GType . Object <$> jsg "SVGFECompositeElement"
newtype SVGFEConvolveMatrixElement = SVGFEConvolveMatrixElement { unSVGFEConvolveMatrixElement :: JSVal }
instance PToJSVal SVGFEConvolveMatrixElement where
pToJSVal = unSVGFEConvolveMatrixElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEConvolveMatrixElement where
pFromJSVal = SVGFEConvolveMatrixElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEConvolveMatrixElement where
toJSVal = return . unSVGFEConvolveMatrixElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEConvolveMatrixElement where
fromJSVal v = fmap SVGFEConvolveMatrixElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEConvolveMatrixElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEConvolveMatrixElement where
makeObject = makeObject . unSVGFEConvolveMatrixElement
instance IsSVGElement SVGFEConvolveMatrixElement
instance IsElement SVGFEConvolveMatrixElement
instance IsNode SVGFEConvolveMatrixElement
instance IsEventTarget SVGFEConvolveMatrixElement
instance IsSlotable SVGFEConvolveMatrixElement
instance IsParentNode SVGFEConvolveMatrixElement
instance IsNonDocumentTypeChildNode SVGFEConvolveMatrixElement
instance IsDocumentAndElementEventHandlers SVGFEConvolveMatrixElement
instance IsChildNode SVGFEConvolveMatrixElement
instance IsAnimatable SVGFEConvolveMatrixElement
instance IsGlobalEventHandlers SVGFEConvolveMatrixElement
instance IsElementCSSInlineStyle SVGFEConvolveMatrixElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEConvolveMatrixElement
instance IsGObject SVGFEConvolveMatrixElement where
typeGType _ = gTypeSVGFEConvolveMatrixElement
{-# INLINE typeGType #-}
noSVGFEConvolveMatrixElement :: Maybe SVGFEConvolveMatrixElement
noSVGFEConvolveMatrixElement = Nothing
{-# INLINE noSVGFEConvolveMatrixElement #-}
gTypeSVGFEConvolveMatrixElement :: JSM GType
gTypeSVGFEConvolveMatrixElement = GType . Object <$> jsg "SVGFEConvolveMatrixElement"
newtype SVGFEDiffuseLightingElement = SVGFEDiffuseLightingElement { unSVGFEDiffuseLightingElement :: JSVal }
instance PToJSVal SVGFEDiffuseLightingElement where
pToJSVal = unSVGFEDiffuseLightingElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEDiffuseLightingElement where
pFromJSVal = SVGFEDiffuseLightingElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEDiffuseLightingElement where
toJSVal = return . unSVGFEDiffuseLightingElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEDiffuseLightingElement where
fromJSVal v = fmap SVGFEDiffuseLightingElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEDiffuseLightingElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEDiffuseLightingElement where
makeObject = makeObject . unSVGFEDiffuseLightingElement
instance IsSVGElement SVGFEDiffuseLightingElement
instance IsElement SVGFEDiffuseLightingElement
instance IsNode SVGFEDiffuseLightingElement
instance IsEventTarget SVGFEDiffuseLightingElement
instance IsSlotable SVGFEDiffuseLightingElement
instance IsParentNode SVGFEDiffuseLightingElement
instance IsNonDocumentTypeChildNode SVGFEDiffuseLightingElement
instance IsDocumentAndElementEventHandlers SVGFEDiffuseLightingElement
instance IsChildNode SVGFEDiffuseLightingElement
instance IsAnimatable SVGFEDiffuseLightingElement
instance IsGlobalEventHandlers SVGFEDiffuseLightingElement
instance IsElementCSSInlineStyle SVGFEDiffuseLightingElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEDiffuseLightingElement
instance IsGObject SVGFEDiffuseLightingElement where
typeGType _ = gTypeSVGFEDiffuseLightingElement
{-# INLINE typeGType #-}
noSVGFEDiffuseLightingElement :: Maybe SVGFEDiffuseLightingElement
noSVGFEDiffuseLightingElement = Nothing
{-# INLINE noSVGFEDiffuseLightingElement #-}
gTypeSVGFEDiffuseLightingElement :: JSM GType
gTypeSVGFEDiffuseLightingElement = GType . Object <$> jsg "SVGFEDiffuseLightingElement"
newtype SVGFEDisplacementMapElement = SVGFEDisplacementMapElement { unSVGFEDisplacementMapElement :: JSVal }
instance PToJSVal SVGFEDisplacementMapElement where
pToJSVal = unSVGFEDisplacementMapElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEDisplacementMapElement where
pFromJSVal = SVGFEDisplacementMapElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEDisplacementMapElement where
toJSVal = return . unSVGFEDisplacementMapElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEDisplacementMapElement where
fromJSVal v = fmap SVGFEDisplacementMapElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEDisplacementMapElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEDisplacementMapElement where
makeObject = makeObject . unSVGFEDisplacementMapElement
instance IsSVGElement SVGFEDisplacementMapElement
instance IsElement SVGFEDisplacementMapElement
instance IsNode SVGFEDisplacementMapElement
instance IsEventTarget SVGFEDisplacementMapElement
instance IsSlotable SVGFEDisplacementMapElement
instance IsParentNode SVGFEDisplacementMapElement
instance IsNonDocumentTypeChildNode SVGFEDisplacementMapElement
instance IsDocumentAndElementEventHandlers SVGFEDisplacementMapElement
instance IsChildNode SVGFEDisplacementMapElement
instance IsAnimatable SVGFEDisplacementMapElement
instance IsGlobalEventHandlers SVGFEDisplacementMapElement
instance IsElementCSSInlineStyle SVGFEDisplacementMapElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEDisplacementMapElement
instance IsGObject SVGFEDisplacementMapElement where
typeGType _ = gTypeSVGFEDisplacementMapElement
{-# INLINE typeGType #-}
noSVGFEDisplacementMapElement :: Maybe SVGFEDisplacementMapElement
noSVGFEDisplacementMapElement = Nothing
{-# INLINE noSVGFEDisplacementMapElement #-}
gTypeSVGFEDisplacementMapElement :: JSM GType
gTypeSVGFEDisplacementMapElement = GType . Object <$> jsg "SVGFEDisplacementMapElement"
newtype SVGFEDistantLightElement = SVGFEDistantLightElement { unSVGFEDistantLightElement :: JSVal }
instance PToJSVal SVGFEDistantLightElement where
pToJSVal = unSVGFEDistantLightElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEDistantLightElement where
pFromJSVal = SVGFEDistantLightElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEDistantLightElement where
toJSVal = return . unSVGFEDistantLightElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEDistantLightElement where
fromJSVal v = fmap SVGFEDistantLightElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEDistantLightElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEDistantLightElement where
makeObject = makeObject . unSVGFEDistantLightElement
instance IsSVGElement SVGFEDistantLightElement
instance IsElement SVGFEDistantLightElement
instance IsNode SVGFEDistantLightElement
instance IsEventTarget SVGFEDistantLightElement
instance IsSlotable SVGFEDistantLightElement
instance IsParentNode SVGFEDistantLightElement
instance IsNonDocumentTypeChildNode SVGFEDistantLightElement
instance IsDocumentAndElementEventHandlers SVGFEDistantLightElement
instance IsChildNode SVGFEDistantLightElement
instance IsAnimatable SVGFEDistantLightElement
instance IsGlobalEventHandlers SVGFEDistantLightElement
instance IsElementCSSInlineStyle SVGFEDistantLightElement
instance IsGObject SVGFEDistantLightElement where
typeGType _ = gTypeSVGFEDistantLightElement
{-# INLINE typeGType #-}
noSVGFEDistantLightElement :: Maybe SVGFEDistantLightElement
noSVGFEDistantLightElement = Nothing
{-# INLINE noSVGFEDistantLightElement #-}
gTypeSVGFEDistantLightElement :: JSM GType
gTypeSVGFEDistantLightElement = GType . Object <$> jsg "SVGFEDistantLightElement"
newtype SVGFEDropShadowElement = SVGFEDropShadowElement { unSVGFEDropShadowElement :: JSVal }
instance PToJSVal SVGFEDropShadowElement where
pToJSVal = unSVGFEDropShadowElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEDropShadowElement where
pFromJSVal = SVGFEDropShadowElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEDropShadowElement where
toJSVal = return . unSVGFEDropShadowElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEDropShadowElement where
fromJSVal v = fmap SVGFEDropShadowElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEDropShadowElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEDropShadowElement where
makeObject = makeObject . unSVGFEDropShadowElement
instance IsSVGElement SVGFEDropShadowElement
instance IsElement SVGFEDropShadowElement
instance IsNode SVGFEDropShadowElement
instance IsEventTarget SVGFEDropShadowElement
instance IsSlotable SVGFEDropShadowElement
instance IsParentNode SVGFEDropShadowElement
instance IsNonDocumentTypeChildNode SVGFEDropShadowElement
instance IsDocumentAndElementEventHandlers SVGFEDropShadowElement
instance IsChildNode SVGFEDropShadowElement
instance IsAnimatable SVGFEDropShadowElement
instance IsGlobalEventHandlers SVGFEDropShadowElement
instance IsElementCSSInlineStyle SVGFEDropShadowElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEDropShadowElement
instance IsGObject SVGFEDropShadowElement where
typeGType _ = gTypeSVGFEDropShadowElement
{-# INLINE typeGType #-}
noSVGFEDropShadowElement :: Maybe SVGFEDropShadowElement
noSVGFEDropShadowElement = Nothing
{-# INLINE noSVGFEDropShadowElement #-}
gTypeSVGFEDropShadowElement :: JSM GType
gTypeSVGFEDropShadowElement = GType . Object <$> jsg "SVGFEDropShadowElement"
newtype SVGFEFloodElement = SVGFEFloodElement { unSVGFEFloodElement :: JSVal }
instance PToJSVal SVGFEFloodElement where
pToJSVal = unSVGFEFloodElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEFloodElement where
pFromJSVal = SVGFEFloodElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEFloodElement where
toJSVal = return . unSVGFEFloodElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEFloodElement where
fromJSVal v = fmap SVGFEFloodElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEFloodElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEFloodElement where
makeObject = makeObject . unSVGFEFloodElement
instance IsSVGElement SVGFEFloodElement
instance IsElement SVGFEFloodElement
instance IsNode SVGFEFloodElement
instance IsEventTarget SVGFEFloodElement
instance IsSlotable SVGFEFloodElement
instance IsParentNode SVGFEFloodElement
instance IsNonDocumentTypeChildNode SVGFEFloodElement
instance IsDocumentAndElementEventHandlers SVGFEFloodElement
instance IsChildNode SVGFEFloodElement
instance IsAnimatable SVGFEFloodElement
instance IsGlobalEventHandlers SVGFEFloodElement
instance IsElementCSSInlineStyle SVGFEFloodElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEFloodElement
instance IsGObject SVGFEFloodElement where
typeGType _ = gTypeSVGFEFloodElement
{-# INLINE typeGType #-}
noSVGFEFloodElement :: Maybe SVGFEFloodElement
noSVGFEFloodElement = Nothing
{-# INLINE noSVGFEFloodElement #-}
gTypeSVGFEFloodElement :: JSM GType
gTypeSVGFEFloodElement = GType . Object <$> jsg "SVGFEFloodElement"
newtype SVGFEFuncAElement = SVGFEFuncAElement { unSVGFEFuncAElement :: JSVal }
instance PToJSVal SVGFEFuncAElement where
pToJSVal = unSVGFEFuncAElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEFuncAElement where
pFromJSVal = SVGFEFuncAElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEFuncAElement where
toJSVal = return . unSVGFEFuncAElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEFuncAElement where
fromJSVal v = fmap SVGFEFuncAElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEFuncAElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEFuncAElement where
makeObject = makeObject . unSVGFEFuncAElement
instance IsSVGComponentTransferFunctionElement SVGFEFuncAElement
instance IsSVGElement SVGFEFuncAElement
instance IsElement SVGFEFuncAElement
instance IsNode SVGFEFuncAElement
instance IsEventTarget SVGFEFuncAElement
instance IsSlotable SVGFEFuncAElement
instance IsParentNode SVGFEFuncAElement
instance IsNonDocumentTypeChildNode SVGFEFuncAElement
instance IsDocumentAndElementEventHandlers SVGFEFuncAElement
instance IsChildNode SVGFEFuncAElement
instance IsAnimatable SVGFEFuncAElement
instance IsGlobalEventHandlers SVGFEFuncAElement
instance IsElementCSSInlineStyle SVGFEFuncAElement
instance IsGObject SVGFEFuncAElement where
typeGType _ = gTypeSVGFEFuncAElement
{-# INLINE typeGType #-}
noSVGFEFuncAElement :: Maybe SVGFEFuncAElement
noSVGFEFuncAElement = Nothing
{-# INLINE noSVGFEFuncAElement #-}
gTypeSVGFEFuncAElement :: JSM GType
gTypeSVGFEFuncAElement = GType . Object <$> jsg "SVGFEFuncAElement"
newtype SVGFEFuncBElement = SVGFEFuncBElement { unSVGFEFuncBElement :: JSVal }
instance PToJSVal SVGFEFuncBElement where
pToJSVal = unSVGFEFuncBElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEFuncBElement where
pFromJSVal = SVGFEFuncBElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEFuncBElement where
toJSVal = return . unSVGFEFuncBElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEFuncBElement where
fromJSVal v = fmap SVGFEFuncBElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEFuncBElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEFuncBElement where
makeObject = makeObject . unSVGFEFuncBElement
instance IsSVGComponentTransferFunctionElement SVGFEFuncBElement
instance IsSVGElement SVGFEFuncBElement
instance IsElement SVGFEFuncBElement
instance IsNode SVGFEFuncBElement
instance IsEventTarget SVGFEFuncBElement
instance IsSlotable SVGFEFuncBElement
instance IsParentNode SVGFEFuncBElement
instance IsNonDocumentTypeChildNode SVGFEFuncBElement
instance IsDocumentAndElementEventHandlers SVGFEFuncBElement
instance IsChildNode SVGFEFuncBElement
instance IsAnimatable SVGFEFuncBElement
instance IsGlobalEventHandlers SVGFEFuncBElement
instance IsElementCSSInlineStyle SVGFEFuncBElement
instance IsGObject SVGFEFuncBElement where
typeGType _ = gTypeSVGFEFuncBElement
{-# INLINE typeGType #-}
noSVGFEFuncBElement :: Maybe SVGFEFuncBElement
noSVGFEFuncBElement = Nothing
{-# INLINE noSVGFEFuncBElement #-}
gTypeSVGFEFuncBElement :: JSM GType
gTypeSVGFEFuncBElement = GType . Object <$> jsg "SVGFEFuncBElement"
newtype SVGFEFuncGElement = SVGFEFuncGElement { unSVGFEFuncGElement :: JSVal }
instance PToJSVal SVGFEFuncGElement where
pToJSVal = unSVGFEFuncGElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEFuncGElement where
pFromJSVal = SVGFEFuncGElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEFuncGElement where
toJSVal = return . unSVGFEFuncGElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEFuncGElement where
fromJSVal v = fmap SVGFEFuncGElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEFuncGElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEFuncGElement where
makeObject = makeObject . unSVGFEFuncGElement
instance IsSVGComponentTransferFunctionElement SVGFEFuncGElement
instance IsSVGElement SVGFEFuncGElement
instance IsElement SVGFEFuncGElement
instance IsNode SVGFEFuncGElement
instance IsEventTarget SVGFEFuncGElement
instance IsSlotable SVGFEFuncGElement
instance IsParentNode SVGFEFuncGElement
instance IsNonDocumentTypeChildNode SVGFEFuncGElement
instance IsDocumentAndElementEventHandlers SVGFEFuncGElement
instance IsChildNode SVGFEFuncGElement
instance IsAnimatable SVGFEFuncGElement
instance IsGlobalEventHandlers SVGFEFuncGElement
instance IsElementCSSInlineStyle SVGFEFuncGElement
instance IsGObject SVGFEFuncGElement where
typeGType _ = gTypeSVGFEFuncGElement
{-# INLINE typeGType #-}
noSVGFEFuncGElement :: Maybe SVGFEFuncGElement
noSVGFEFuncGElement = Nothing
{-# INLINE noSVGFEFuncGElement #-}
gTypeSVGFEFuncGElement :: JSM GType
gTypeSVGFEFuncGElement = GType . Object <$> jsg "SVGFEFuncGElement"
newtype SVGFEFuncRElement = SVGFEFuncRElement { unSVGFEFuncRElement :: JSVal }
instance PToJSVal SVGFEFuncRElement where
pToJSVal = unSVGFEFuncRElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEFuncRElement where
pFromJSVal = SVGFEFuncRElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEFuncRElement where
toJSVal = return . unSVGFEFuncRElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEFuncRElement where
fromJSVal v = fmap SVGFEFuncRElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEFuncRElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEFuncRElement where
makeObject = makeObject . unSVGFEFuncRElement
instance IsSVGComponentTransferFunctionElement SVGFEFuncRElement
instance IsSVGElement SVGFEFuncRElement
instance IsElement SVGFEFuncRElement
instance IsNode SVGFEFuncRElement
instance IsEventTarget SVGFEFuncRElement
instance IsSlotable SVGFEFuncRElement
instance IsParentNode SVGFEFuncRElement
instance IsNonDocumentTypeChildNode SVGFEFuncRElement
instance IsDocumentAndElementEventHandlers SVGFEFuncRElement
instance IsChildNode SVGFEFuncRElement
instance IsAnimatable SVGFEFuncRElement
instance IsGlobalEventHandlers SVGFEFuncRElement
instance IsElementCSSInlineStyle SVGFEFuncRElement
instance IsGObject SVGFEFuncRElement where
typeGType _ = gTypeSVGFEFuncRElement
{-# INLINE typeGType #-}
noSVGFEFuncRElement :: Maybe SVGFEFuncRElement
noSVGFEFuncRElement = Nothing
{-# INLINE noSVGFEFuncRElement #-}
gTypeSVGFEFuncRElement :: JSM GType
gTypeSVGFEFuncRElement = GType . Object <$> jsg "SVGFEFuncRElement"
newtype SVGFEGaussianBlurElement = SVGFEGaussianBlurElement { unSVGFEGaussianBlurElement :: JSVal }
instance PToJSVal SVGFEGaussianBlurElement where
pToJSVal = unSVGFEGaussianBlurElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEGaussianBlurElement where
pFromJSVal = SVGFEGaussianBlurElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEGaussianBlurElement where
toJSVal = return . unSVGFEGaussianBlurElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEGaussianBlurElement where
fromJSVal v = fmap SVGFEGaussianBlurElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEGaussianBlurElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEGaussianBlurElement where
makeObject = makeObject . unSVGFEGaussianBlurElement
instance IsSVGElement SVGFEGaussianBlurElement
instance IsElement SVGFEGaussianBlurElement
instance IsNode SVGFEGaussianBlurElement
instance IsEventTarget SVGFEGaussianBlurElement
instance IsSlotable SVGFEGaussianBlurElement
instance IsParentNode SVGFEGaussianBlurElement
instance IsNonDocumentTypeChildNode SVGFEGaussianBlurElement
instance IsDocumentAndElementEventHandlers SVGFEGaussianBlurElement
instance IsChildNode SVGFEGaussianBlurElement
instance IsAnimatable SVGFEGaussianBlurElement
instance IsGlobalEventHandlers SVGFEGaussianBlurElement
instance IsElementCSSInlineStyle SVGFEGaussianBlurElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEGaussianBlurElement
instance IsGObject SVGFEGaussianBlurElement where
typeGType _ = gTypeSVGFEGaussianBlurElement
{-# INLINE typeGType #-}
noSVGFEGaussianBlurElement :: Maybe SVGFEGaussianBlurElement
noSVGFEGaussianBlurElement = Nothing
{-# INLINE noSVGFEGaussianBlurElement #-}
gTypeSVGFEGaussianBlurElement :: JSM GType
gTypeSVGFEGaussianBlurElement = GType . Object <$> jsg "SVGFEGaussianBlurElement"
newtype SVGFEImageElement = SVGFEImageElement { unSVGFEImageElement :: JSVal }
instance PToJSVal SVGFEImageElement where
pToJSVal = unSVGFEImageElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEImageElement where
pFromJSVal = SVGFEImageElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEImageElement where
toJSVal = return . unSVGFEImageElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEImageElement where
fromJSVal v = fmap SVGFEImageElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEImageElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEImageElement where
makeObject = makeObject . unSVGFEImageElement
instance IsSVGElement SVGFEImageElement
instance IsElement SVGFEImageElement
instance IsNode SVGFEImageElement
instance IsEventTarget SVGFEImageElement
instance IsSlotable SVGFEImageElement
instance IsParentNode SVGFEImageElement
instance IsNonDocumentTypeChildNode SVGFEImageElement
instance IsDocumentAndElementEventHandlers SVGFEImageElement
instance IsChildNode SVGFEImageElement
instance IsAnimatable SVGFEImageElement
instance IsGlobalEventHandlers SVGFEImageElement
instance IsElementCSSInlineStyle SVGFEImageElement
instance IsSVGURIReference SVGFEImageElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEImageElement
instance IsSVGExternalResourcesRequired SVGFEImageElement
instance IsGObject SVGFEImageElement where
typeGType _ = gTypeSVGFEImageElement
{-# INLINE typeGType #-}
noSVGFEImageElement :: Maybe SVGFEImageElement
noSVGFEImageElement = Nothing
{-# INLINE noSVGFEImageElement #-}
gTypeSVGFEImageElement :: JSM GType
gTypeSVGFEImageElement = GType . Object <$> jsg "SVGFEImageElement"
newtype SVGFEMergeElement = SVGFEMergeElement { unSVGFEMergeElement :: JSVal }
instance PToJSVal SVGFEMergeElement where
pToJSVal = unSVGFEMergeElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEMergeElement where
pFromJSVal = SVGFEMergeElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEMergeElement where
toJSVal = return . unSVGFEMergeElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEMergeElement where
fromJSVal v = fmap SVGFEMergeElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEMergeElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEMergeElement where
makeObject = makeObject . unSVGFEMergeElement
instance IsSVGElement SVGFEMergeElement
instance IsElement SVGFEMergeElement
instance IsNode SVGFEMergeElement
instance IsEventTarget SVGFEMergeElement
instance IsSlotable SVGFEMergeElement
instance IsParentNode SVGFEMergeElement
instance IsNonDocumentTypeChildNode SVGFEMergeElement
instance IsDocumentAndElementEventHandlers SVGFEMergeElement
instance IsChildNode SVGFEMergeElement
instance IsAnimatable SVGFEMergeElement
instance IsGlobalEventHandlers SVGFEMergeElement
instance IsElementCSSInlineStyle SVGFEMergeElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEMergeElement
instance IsGObject SVGFEMergeElement where
typeGType _ = gTypeSVGFEMergeElement
{-# INLINE typeGType #-}
noSVGFEMergeElement :: Maybe SVGFEMergeElement
noSVGFEMergeElement = Nothing
{-# INLINE noSVGFEMergeElement #-}
gTypeSVGFEMergeElement :: JSM GType
gTypeSVGFEMergeElement = GType . Object <$> jsg "SVGFEMergeElement"
newtype SVGFEMergeNodeElement = SVGFEMergeNodeElement { unSVGFEMergeNodeElement :: JSVal }
instance PToJSVal SVGFEMergeNodeElement where
pToJSVal = unSVGFEMergeNodeElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEMergeNodeElement where
pFromJSVal = SVGFEMergeNodeElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEMergeNodeElement where
toJSVal = return . unSVGFEMergeNodeElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEMergeNodeElement where
fromJSVal v = fmap SVGFEMergeNodeElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEMergeNodeElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEMergeNodeElement where
makeObject = makeObject . unSVGFEMergeNodeElement
instance IsSVGElement SVGFEMergeNodeElement
instance IsElement SVGFEMergeNodeElement
instance IsNode SVGFEMergeNodeElement
instance IsEventTarget SVGFEMergeNodeElement
instance IsSlotable SVGFEMergeNodeElement
instance IsParentNode SVGFEMergeNodeElement
instance IsNonDocumentTypeChildNode SVGFEMergeNodeElement
instance IsDocumentAndElementEventHandlers SVGFEMergeNodeElement
instance IsChildNode SVGFEMergeNodeElement
instance IsAnimatable SVGFEMergeNodeElement
instance IsGlobalEventHandlers SVGFEMergeNodeElement
instance IsElementCSSInlineStyle SVGFEMergeNodeElement
instance IsGObject SVGFEMergeNodeElement where
typeGType _ = gTypeSVGFEMergeNodeElement
{-# INLINE typeGType #-}
noSVGFEMergeNodeElement :: Maybe SVGFEMergeNodeElement
noSVGFEMergeNodeElement = Nothing
{-# INLINE noSVGFEMergeNodeElement #-}
gTypeSVGFEMergeNodeElement :: JSM GType
gTypeSVGFEMergeNodeElement = GType . Object <$> jsg "SVGFEMergeNodeElement"
newtype SVGFEMorphologyElement = SVGFEMorphologyElement { unSVGFEMorphologyElement :: JSVal }
instance PToJSVal SVGFEMorphologyElement where
pToJSVal = unSVGFEMorphologyElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEMorphologyElement where
pFromJSVal = SVGFEMorphologyElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEMorphologyElement where
toJSVal = return . unSVGFEMorphologyElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEMorphologyElement where
fromJSVal v = fmap SVGFEMorphologyElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEMorphologyElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEMorphologyElement where
makeObject = makeObject . unSVGFEMorphologyElement
instance IsSVGElement SVGFEMorphologyElement
instance IsElement SVGFEMorphologyElement
instance IsNode SVGFEMorphologyElement
instance IsEventTarget SVGFEMorphologyElement
instance IsSlotable SVGFEMorphologyElement
instance IsParentNode SVGFEMorphologyElement
instance IsNonDocumentTypeChildNode SVGFEMorphologyElement
instance IsDocumentAndElementEventHandlers SVGFEMorphologyElement
instance IsChildNode SVGFEMorphologyElement
instance IsAnimatable SVGFEMorphologyElement
instance IsGlobalEventHandlers SVGFEMorphologyElement
instance IsElementCSSInlineStyle SVGFEMorphologyElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEMorphologyElement
instance IsGObject SVGFEMorphologyElement where
typeGType _ = gTypeSVGFEMorphologyElement
{-# INLINE typeGType #-}
noSVGFEMorphologyElement :: Maybe SVGFEMorphologyElement
noSVGFEMorphologyElement = Nothing
{-# INLINE noSVGFEMorphologyElement #-}
gTypeSVGFEMorphologyElement :: JSM GType
gTypeSVGFEMorphologyElement = GType . Object <$> jsg "SVGFEMorphologyElement"
newtype SVGFEOffsetElement = SVGFEOffsetElement { unSVGFEOffsetElement :: JSVal }
instance PToJSVal SVGFEOffsetElement where
pToJSVal = unSVGFEOffsetElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEOffsetElement where
pFromJSVal = SVGFEOffsetElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEOffsetElement where
toJSVal = return . unSVGFEOffsetElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEOffsetElement where
fromJSVal v = fmap SVGFEOffsetElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEOffsetElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEOffsetElement where
makeObject = makeObject . unSVGFEOffsetElement
instance IsSVGElement SVGFEOffsetElement
instance IsElement SVGFEOffsetElement
instance IsNode SVGFEOffsetElement
instance IsEventTarget SVGFEOffsetElement
instance IsSlotable SVGFEOffsetElement
instance IsParentNode SVGFEOffsetElement
instance IsNonDocumentTypeChildNode SVGFEOffsetElement
instance IsDocumentAndElementEventHandlers SVGFEOffsetElement
instance IsChildNode SVGFEOffsetElement
instance IsAnimatable SVGFEOffsetElement
instance IsGlobalEventHandlers SVGFEOffsetElement
instance IsElementCSSInlineStyle SVGFEOffsetElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFEOffsetElement
instance IsGObject SVGFEOffsetElement where
typeGType _ = gTypeSVGFEOffsetElement
{-# INLINE typeGType #-}
noSVGFEOffsetElement :: Maybe SVGFEOffsetElement
noSVGFEOffsetElement = Nothing
{-# INLINE noSVGFEOffsetElement #-}
gTypeSVGFEOffsetElement :: JSM GType
gTypeSVGFEOffsetElement = GType . Object <$> jsg "SVGFEOffsetElement"
newtype SVGFEPointLightElement = SVGFEPointLightElement { unSVGFEPointLightElement :: JSVal }
instance PToJSVal SVGFEPointLightElement where
pToJSVal = unSVGFEPointLightElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFEPointLightElement where
pFromJSVal = SVGFEPointLightElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFEPointLightElement where
toJSVal = return . unSVGFEPointLightElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFEPointLightElement where
fromJSVal v = fmap SVGFEPointLightElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFEPointLightElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFEPointLightElement where
makeObject = makeObject . unSVGFEPointLightElement
instance IsSVGElement SVGFEPointLightElement
instance IsElement SVGFEPointLightElement
instance IsNode SVGFEPointLightElement
instance IsEventTarget SVGFEPointLightElement
instance IsSlotable SVGFEPointLightElement
instance IsParentNode SVGFEPointLightElement
instance IsNonDocumentTypeChildNode SVGFEPointLightElement
instance IsDocumentAndElementEventHandlers SVGFEPointLightElement
instance IsChildNode SVGFEPointLightElement
instance IsAnimatable SVGFEPointLightElement
instance IsGlobalEventHandlers SVGFEPointLightElement
instance IsElementCSSInlineStyle SVGFEPointLightElement
instance IsGObject SVGFEPointLightElement where
typeGType _ = gTypeSVGFEPointLightElement
{-# INLINE typeGType #-}
noSVGFEPointLightElement :: Maybe SVGFEPointLightElement
noSVGFEPointLightElement = Nothing
{-# INLINE noSVGFEPointLightElement #-}
gTypeSVGFEPointLightElement :: JSM GType
gTypeSVGFEPointLightElement = GType . Object <$> jsg "SVGFEPointLightElement"
newtype SVGFESpecularLightingElement = SVGFESpecularLightingElement { unSVGFESpecularLightingElement :: JSVal }
instance PToJSVal SVGFESpecularLightingElement where
pToJSVal = unSVGFESpecularLightingElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFESpecularLightingElement where
pFromJSVal = SVGFESpecularLightingElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFESpecularLightingElement where
toJSVal = return . unSVGFESpecularLightingElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFESpecularLightingElement where
fromJSVal v = fmap SVGFESpecularLightingElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFESpecularLightingElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFESpecularLightingElement where
makeObject = makeObject . unSVGFESpecularLightingElement
instance IsSVGElement SVGFESpecularLightingElement
instance IsElement SVGFESpecularLightingElement
instance IsNode SVGFESpecularLightingElement
instance IsEventTarget SVGFESpecularLightingElement
instance IsSlotable SVGFESpecularLightingElement
instance IsParentNode SVGFESpecularLightingElement
instance IsNonDocumentTypeChildNode SVGFESpecularLightingElement
instance IsDocumentAndElementEventHandlers SVGFESpecularLightingElement
instance IsChildNode SVGFESpecularLightingElement
instance IsAnimatable SVGFESpecularLightingElement
instance IsGlobalEventHandlers SVGFESpecularLightingElement
instance IsElementCSSInlineStyle SVGFESpecularLightingElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFESpecularLightingElement
instance IsGObject SVGFESpecularLightingElement where
typeGType _ = gTypeSVGFESpecularLightingElement
{-# INLINE typeGType #-}
noSVGFESpecularLightingElement :: Maybe SVGFESpecularLightingElement
noSVGFESpecularLightingElement = Nothing
{-# INLINE noSVGFESpecularLightingElement #-}
gTypeSVGFESpecularLightingElement :: JSM GType
gTypeSVGFESpecularLightingElement = GType . Object <$> jsg "SVGFESpecularLightingElement"
newtype SVGFESpotLightElement = SVGFESpotLightElement { unSVGFESpotLightElement :: JSVal }
instance PToJSVal SVGFESpotLightElement where
pToJSVal = unSVGFESpotLightElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFESpotLightElement where
pFromJSVal = SVGFESpotLightElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFESpotLightElement where
toJSVal = return . unSVGFESpotLightElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFESpotLightElement where
fromJSVal v = fmap SVGFESpotLightElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFESpotLightElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFESpotLightElement where
makeObject = makeObject . unSVGFESpotLightElement
instance IsSVGElement SVGFESpotLightElement
instance IsElement SVGFESpotLightElement
instance IsNode SVGFESpotLightElement
instance IsEventTarget SVGFESpotLightElement
instance IsSlotable SVGFESpotLightElement
instance IsParentNode SVGFESpotLightElement
instance IsNonDocumentTypeChildNode SVGFESpotLightElement
instance IsDocumentAndElementEventHandlers SVGFESpotLightElement
instance IsChildNode SVGFESpotLightElement
instance IsAnimatable SVGFESpotLightElement
instance IsGlobalEventHandlers SVGFESpotLightElement
instance IsElementCSSInlineStyle SVGFESpotLightElement
instance IsGObject SVGFESpotLightElement where
typeGType _ = gTypeSVGFESpotLightElement
{-# INLINE typeGType #-}
noSVGFESpotLightElement :: Maybe SVGFESpotLightElement
noSVGFESpotLightElement = Nothing
{-# INLINE noSVGFESpotLightElement #-}
gTypeSVGFESpotLightElement :: JSM GType
gTypeSVGFESpotLightElement = GType . Object <$> jsg "SVGFESpotLightElement"
newtype SVGFETileElement = SVGFETileElement { unSVGFETileElement :: JSVal }
instance PToJSVal SVGFETileElement where
pToJSVal = unSVGFETileElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFETileElement where
pFromJSVal = SVGFETileElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFETileElement where
toJSVal = return . unSVGFETileElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFETileElement where
fromJSVal v = fmap SVGFETileElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFETileElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFETileElement where
makeObject = makeObject . unSVGFETileElement
instance IsSVGElement SVGFETileElement
instance IsElement SVGFETileElement
instance IsNode SVGFETileElement
instance IsEventTarget SVGFETileElement
instance IsSlotable SVGFETileElement
instance IsParentNode SVGFETileElement
instance IsNonDocumentTypeChildNode SVGFETileElement
instance IsDocumentAndElementEventHandlers SVGFETileElement
instance IsChildNode SVGFETileElement
instance IsAnimatable SVGFETileElement
instance IsGlobalEventHandlers SVGFETileElement
instance IsElementCSSInlineStyle SVGFETileElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFETileElement
instance IsGObject SVGFETileElement where
typeGType _ = gTypeSVGFETileElement
{-# INLINE typeGType #-}
noSVGFETileElement :: Maybe SVGFETileElement
noSVGFETileElement = Nothing
{-# INLINE noSVGFETileElement #-}
gTypeSVGFETileElement :: JSM GType
gTypeSVGFETileElement = GType . Object <$> jsg "SVGFETileElement"
newtype SVGFETurbulenceElement = SVGFETurbulenceElement { unSVGFETurbulenceElement :: JSVal }
instance PToJSVal SVGFETurbulenceElement where
pToJSVal = unSVGFETurbulenceElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFETurbulenceElement where
pFromJSVal = SVGFETurbulenceElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFETurbulenceElement where
toJSVal = return . unSVGFETurbulenceElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFETurbulenceElement where
fromJSVal v = fmap SVGFETurbulenceElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFETurbulenceElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFETurbulenceElement where
makeObject = makeObject . unSVGFETurbulenceElement
instance IsSVGElement SVGFETurbulenceElement
instance IsElement SVGFETurbulenceElement
instance IsNode SVGFETurbulenceElement
instance IsEventTarget SVGFETurbulenceElement
instance IsSlotable SVGFETurbulenceElement
instance IsParentNode SVGFETurbulenceElement
instance IsNonDocumentTypeChildNode SVGFETurbulenceElement
instance IsDocumentAndElementEventHandlers SVGFETurbulenceElement
instance IsChildNode SVGFETurbulenceElement
instance IsAnimatable SVGFETurbulenceElement
instance IsGlobalEventHandlers SVGFETurbulenceElement
instance IsElementCSSInlineStyle SVGFETurbulenceElement
instance IsSVGFilterPrimitiveStandardAttributes SVGFETurbulenceElement
instance IsGObject SVGFETurbulenceElement where
typeGType _ = gTypeSVGFETurbulenceElement
{-# INLINE typeGType #-}
noSVGFETurbulenceElement :: Maybe SVGFETurbulenceElement
noSVGFETurbulenceElement = Nothing
{-# INLINE noSVGFETurbulenceElement #-}
gTypeSVGFETurbulenceElement :: JSM GType
gTypeSVGFETurbulenceElement = GType . Object <$> jsg "SVGFETurbulenceElement"
newtype SVGFilterElement = SVGFilterElement { unSVGFilterElement :: JSVal }
instance PToJSVal SVGFilterElement where
pToJSVal = unSVGFilterElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFilterElement where
pFromJSVal = SVGFilterElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFilterElement where
toJSVal = return . unSVGFilterElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFilterElement where
fromJSVal v = fmap SVGFilterElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFilterElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFilterElement where
makeObject = makeObject . unSVGFilterElement
instance IsSVGElement SVGFilterElement
instance IsElement SVGFilterElement
instance IsNode SVGFilterElement
instance IsEventTarget SVGFilterElement
instance IsSlotable SVGFilterElement
instance IsParentNode SVGFilterElement
instance IsNonDocumentTypeChildNode SVGFilterElement
instance IsDocumentAndElementEventHandlers SVGFilterElement
instance IsChildNode SVGFilterElement
instance IsAnimatable SVGFilterElement
instance IsGlobalEventHandlers SVGFilterElement
instance IsElementCSSInlineStyle SVGFilterElement
instance IsSVGURIReference SVGFilterElement
instance IsSVGExternalResourcesRequired SVGFilterElement
instance IsGObject SVGFilterElement where
typeGType _ = gTypeSVGFilterElement
{-# INLINE typeGType #-}
noSVGFilterElement :: Maybe SVGFilterElement
noSVGFilterElement = Nothing
{-# INLINE noSVGFilterElement #-}
gTypeSVGFilterElement :: JSM GType
gTypeSVGFilterElement = GType . Object <$> jsg "SVGFilterElement"
newtype SVGFilterPrimitiveStandardAttributes = SVGFilterPrimitiveStandardAttributes { unSVGFilterPrimitiveStandardAttributes :: JSVal }
instance PToJSVal SVGFilterPrimitiveStandardAttributes where
pToJSVal = unSVGFilterPrimitiveStandardAttributes
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFilterPrimitiveStandardAttributes where
pFromJSVal = SVGFilterPrimitiveStandardAttributes
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFilterPrimitiveStandardAttributes where
toJSVal = return . unSVGFilterPrimitiveStandardAttributes
{-# INLINE toJSVal #-}
instance FromJSVal SVGFilterPrimitiveStandardAttributes where
fromJSVal v = fmap SVGFilterPrimitiveStandardAttributes <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFilterPrimitiveStandardAttributes
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFilterPrimitiveStandardAttributes where
makeObject = makeObject . unSVGFilterPrimitiveStandardAttributes
class (IsGObject o) => IsSVGFilterPrimitiveStandardAttributes o
toSVGFilterPrimitiveStandardAttributes :: IsSVGFilterPrimitiveStandardAttributes o => o -> SVGFilterPrimitiveStandardAttributes
toSVGFilterPrimitiveStandardAttributes = SVGFilterPrimitiveStandardAttributes . coerce
instance IsSVGFilterPrimitiveStandardAttributes SVGFilterPrimitiveStandardAttributes
instance IsGObject SVGFilterPrimitiveStandardAttributes where
typeGType _ = gTypeSVGFilterPrimitiveStandardAttributes
{-# INLINE typeGType #-}
noSVGFilterPrimitiveStandardAttributes :: Maybe SVGFilterPrimitiveStandardAttributes
noSVGFilterPrimitiveStandardAttributes = Nothing
{-# INLINE noSVGFilterPrimitiveStandardAttributes #-}
gTypeSVGFilterPrimitiveStandardAttributes :: JSM GType
gTypeSVGFilterPrimitiveStandardAttributes = GType . Object <$> jsg "SVGFilterPrimitiveStandardAttributes"
newtype SVGFitToViewBox = SVGFitToViewBox { unSVGFitToViewBox :: JSVal }
instance PToJSVal SVGFitToViewBox where
pToJSVal = unSVGFitToViewBox
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFitToViewBox where
pFromJSVal = SVGFitToViewBox
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFitToViewBox where
toJSVal = return . unSVGFitToViewBox
{-# INLINE toJSVal #-}
instance FromJSVal SVGFitToViewBox where
fromJSVal v = fmap SVGFitToViewBox <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFitToViewBox
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFitToViewBox where
makeObject = makeObject . unSVGFitToViewBox
class (IsGObject o) => IsSVGFitToViewBox o
toSVGFitToViewBox :: IsSVGFitToViewBox o => o -> SVGFitToViewBox
toSVGFitToViewBox = SVGFitToViewBox . coerce
instance IsSVGFitToViewBox SVGFitToViewBox
instance IsGObject SVGFitToViewBox where
typeGType _ = gTypeSVGFitToViewBox
{-# INLINE typeGType #-}
noSVGFitToViewBox :: Maybe SVGFitToViewBox
noSVGFitToViewBox = Nothing
{-# INLINE noSVGFitToViewBox #-}
gTypeSVGFitToViewBox :: JSM GType
gTypeSVGFitToViewBox = GType . Object <$> jsg "SVGFitToViewBox"
newtype SVGFontElement = SVGFontElement { unSVGFontElement :: JSVal }
instance PToJSVal SVGFontElement where
pToJSVal = unSVGFontElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFontElement where
pFromJSVal = SVGFontElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFontElement where
toJSVal = return . unSVGFontElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFontElement where
fromJSVal v = fmap SVGFontElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFontElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFontElement where
makeObject = makeObject . unSVGFontElement
instance IsSVGElement SVGFontElement
instance IsElement SVGFontElement
instance IsNode SVGFontElement
instance IsEventTarget SVGFontElement
instance IsSlotable SVGFontElement
instance IsParentNode SVGFontElement
instance IsNonDocumentTypeChildNode SVGFontElement
instance IsDocumentAndElementEventHandlers SVGFontElement
instance IsChildNode SVGFontElement
instance IsAnimatable SVGFontElement
instance IsGlobalEventHandlers SVGFontElement
instance IsElementCSSInlineStyle SVGFontElement
instance IsGObject SVGFontElement where
typeGType _ = gTypeSVGFontElement
{-# INLINE typeGType #-}
noSVGFontElement :: Maybe SVGFontElement
noSVGFontElement = Nothing
{-# INLINE noSVGFontElement #-}
gTypeSVGFontElement :: JSM GType
gTypeSVGFontElement = GType . Object <$> jsg "SVGFontElement"
newtype SVGFontFaceElement = SVGFontFaceElement { unSVGFontFaceElement :: JSVal }
instance PToJSVal SVGFontFaceElement where
pToJSVal = unSVGFontFaceElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFontFaceElement where
pFromJSVal = SVGFontFaceElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFontFaceElement where
toJSVal = return . unSVGFontFaceElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFontFaceElement where
fromJSVal v = fmap SVGFontFaceElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFontFaceElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFontFaceElement where
makeObject = makeObject . unSVGFontFaceElement
instance IsSVGElement SVGFontFaceElement
instance IsElement SVGFontFaceElement
instance IsNode SVGFontFaceElement
instance IsEventTarget SVGFontFaceElement
instance IsSlotable SVGFontFaceElement
instance IsParentNode SVGFontFaceElement
instance IsNonDocumentTypeChildNode SVGFontFaceElement
instance IsDocumentAndElementEventHandlers SVGFontFaceElement
instance IsChildNode SVGFontFaceElement
instance IsAnimatable SVGFontFaceElement
instance IsGlobalEventHandlers SVGFontFaceElement
instance IsElementCSSInlineStyle SVGFontFaceElement
instance IsGObject SVGFontFaceElement where
typeGType _ = gTypeSVGFontFaceElement
{-# INLINE typeGType #-}
noSVGFontFaceElement :: Maybe SVGFontFaceElement
noSVGFontFaceElement = Nothing
{-# INLINE noSVGFontFaceElement #-}
gTypeSVGFontFaceElement :: JSM GType
gTypeSVGFontFaceElement = GType . Object <$> jsg "SVGFontFaceElement"
newtype SVGFontFaceFormatElement = SVGFontFaceFormatElement { unSVGFontFaceFormatElement :: JSVal }
instance PToJSVal SVGFontFaceFormatElement where
pToJSVal = unSVGFontFaceFormatElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFontFaceFormatElement where
pFromJSVal = SVGFontFaceFormatElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFontFaceFormatElement where
toJSVal = return . unSVGFontFaceFormatElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFontFaceFormatElement where
fromJSVal v = fmap SVGFontFaceFormatElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFontFaceFormatElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFontFaceFormatElement where
makeObject = makeObject . unSVGFontFaceFormatElement
instance IsSVGElement SVGFontFaceFormatElement
instance IsElement SVGFontFaceFormatElement
instance IsNode SVGFontFaceFormatElement
instance IsEventTarget SVGFontFaceFormatElement
instance IsSlotable SVGFontFaceFormatElement
instance IsParentNode SVGFontFaceFormatElement
instance IsNonDocumentTypeChildNode SVGFontFaceFormatElement
instance IsDocumentAndElementEventHandlers SVGFontFaceFormatElement
instance IsChildNode SVGFontFaceFormatElement
instance IsAnimatable SVGFontFaceFormatElement
instance IsGlobalEventHandlers SVGFontFaceFormatElement
instance IsElementCSSInlineStyle SVGFontFaceFormatElement
instance IsGObject SVGFontFaceFormatElement where
typeGType _ = gTypeSVGFontFaceFormatElement
{-# INLINE typeGType #-}
noSVGFontFaceFormatElement :: Maybe SVGFontFaceFormatElement
noSVGFontFaceFormatElement = Nothing
{-# INLINE noSVGFontFaceFormatElement #-}
gTypeSVGFontFaceFormatElement :: JSM GType
gTypeSVGFontFaceFormatElement = GType . Object <$> jsg "SVGFontFaceFormatElement"
newtype SVGFontFaceNameElement = SVGFontFaceNameElement { unSVGFontFaceNameElement :: JSVal }
instance PToJSVal SVGFontFaceNameElement where
pToJSVal = unSVGFontFaceNameElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFontFaceNameElement where
pFromJSVal = SVGFontFaceNameElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFontFaceNameElement where
toJSVal = return . unSVGFontFaceNameElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFontFaceNameElement where
fromJSVal v = fmap SVGFontFaceNameElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFontFaceNameElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFontFaceNameElement where
makeObject = makeObject . unSVGFontFaceNameElement
instance IsSVGElement SVGFontFaceNameElement
instance IsElement SVGFontFaceNameElement
instance IsNode SVGFontFaceNameElement
instance IsEventTarget SVGFontFaceNameElement
instance IsSlotable SVGFontFaceNameElement
instance IsParentNode SVGFontFaceNameElement
instance IsNonDocumentTypeChildNode SVGFontFaceNameElement
instance IsDocumentAndElementEventHandlers SVGFontFaceNameElement
instance IsChildNode SVGFontFaceNameElement
instance IsAnimatable SVGFontFaceNameElement
instance IsGlobalEventHandlers SVGFontFaceNameElement
instance IsElementCSSInlineStyle SVGFontFaceNameElement
instance IsGObject SVGFontFaceNameElement where
typeGType _ = gTypeSVGFontFaceNameElement
{-# INLINE typeGType #-}
noSVGFontFaceNameElement :: Maybe SVGFontFaceNameElement
noSVGFontFaceNameElement = Nothing
{-# INLINE noSVGFontFaceNameElement #-}
gTypeSVGFontFaceNameElement :: JSM GType
gTypeSVGFontFaceNameElement = GType . Object <$> jsg "SVGFontFaceNameElement"
newtype SVGFontFaceSrcElement = SVGFontFaceSrcElement { unSVGFontFaceSrcElement :: JSVal }
instance PToJSVal SVGFontFaceSrcElement where
pToJSVal = unSVGFontFaceSrcElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFontFaceSrcElement where
pFromJSVal = SVGFontFaceSrcElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFontFaceSrcElement where
toJSVal = return . unSVGFontFaceSrcElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFontFaceSrcElement where
fromJSVal v = fmap SVGFontFaceSrcElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFontFaceSrcElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFontFaceSrcElement where
makeObject = makeObject . unSVGFontFaceSrcElement
instance IsSVGElement SVGFontFaceSrcElement
instance IsElement SVGFontFaceSrcElement
instance IsNode SVGFontFaceSrcElement
instance IsEventTarget SVGFontFaceSrcElement
instance IsSlotable SVGFontFaceSrcElement
instance IsParentNode SVGFontFaceSrcElement
instance IsNonDocumentTypeChildNode SVGFontFaceSrcElement
instance IsDocumentAndElementEventHandlers SVGFontFaceSrcElement
instance IsChildNode SVGFontFaceSrcElement
instance IsAnimatable SVGFontFaceSrcElement
instance IsGlobalEventHandlers SVGFontFaceSrcElement
instance IsElementCSSInlineStyle SVGFontFaceSrcElement
instance IsGObject SVGFontFaceSrcElement where
typeGType _ = gTypeSVGFontFaceSrcElement
{-# INLINE typeGType #-}
noSVGFontFaceSrcElement :: Maybe SVGFontFaceSrcElement
noSVGFontFaceSrcElement = Nothing
{-# INLINE noSVGFontFaceSrcElement #-}
gTypeSVGFontFaceSrcElement :: JSM GType
gTypeSVGFontFaceSrcElement = GType . Object <$> jsg "SVGFontFaceSrcElement"
newtype SVGFontFaceUriElement = SVGFontFaceUriElement { unSVGFontFaceUriElement :: JSVal }
instance PToJSVal SVGFontFaceUriElement where
pToJSVal = unSVGFontFaceUriElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGFontFaceUriElement where
pFromJSVal = SVGFontFaceUriElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGFontFaceUriElement where
toJSVal = return . unSVGFontFaceUriElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGFontFaceUriElement where
fromJSVal v = fmap SVGFontFaceUriElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGFontFaceUriElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGFontFaceUriElement where
makeObject = makeObject . unSVGFontFaceUriElement
instance IsSVGElement SVGFontFaceUriElement
instance IsElement SVGFontFaceUriElement
instance IsNode SVGFontFaceUriElement
instance IsEventTarget SVGFontFaceUriElement
instance IsSlotable SVGFontFaceUriElement
instance IsParentNode SVGFontFaceUriElement
instance IsNonDocumentTypeChildNode SVGFontFaceUriElement
instance IsDocumentAndElementEventHandlers SVGFontFaceUriElement
instance IsChildNode SVGFontFaceUriElement
instance IsAnimatable SVGFontFaceUriElement
instance IsGlobalEventHandlers SVGFontFaceUriElement
instance IsElementCSSInlineStyle SVGFontFaceUriElement
instance IsGObject SVGFontFaceUriElement where
typeGType _ = gTypeSVGFontFaceUriElement
{-# INLINE typeGType #-}
noSVGFontFaceUriElement :: Maybe SVGFontFaceUriElement
noSVGFontFaceUriElement = Nothing
{-# INLINE noSVGFontFaceUriElement #-}
gTypeSVGFontFaceUriElement :: JSM GType
gTypeSVGFontFaceUriElement = GType . Object <$> jsg "SVGFontFaceUriElement"
newtype SVGForeignObjectElement = SVGForeignObjectElement { unSVGForeignObjectElement :: JSVal }
instance PToJSVal SVGForeignObjectElement where
pToJSVal = unSVGForeignObjectElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGForeignObjectElement where
pFromJSVal = SVGForeignObjectElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGForeignObjectElement where
toJSVal = return . unSVGForeignObjectElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGForeignObjectElement where
fromJSVal v = fmap SVGForeignObjectElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGForeignObjectElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGForeignObjectElement where
makeObject = makeObject . unSVGForeignObjectElement
instance IsSVGGraphicsElement SVGForeignObjectElement
instance IsSVGElement SVGForeignObjectElement
instance IsElement SVGForeignObjectElement
instance IsNode SVGForeignObjectElement
instance IsEventTarget SVGForeignObjectElement
instance IsSlotable SVGForeignObjectElement
instance IsParentNode SVGForeignObjectElement
instance IsNonDocumentTypeChildNode SVGForeignObjectElement
instance IsDocumentAndElementEventHandlers SVGForeignObjectElement
instance IsChildNode SVGForeignObjectElement
instance IsAnimatable SVGForeignObjectElement
instance IsGlobalEventHandlers SVGForeignObjectElement
instance IsElementCSSInlineStyle SVGForeignObjectElement
instance IsSVGTests SVGForeignObjectElement
instance IsSVGExternalResourcesRequired SVGForeignObjectElement
instance IsGObject SVGForeignObjectElement where
typeGType _ = gTypeSVGForeignObjectElement
{-# INLINE typeGType #-}
noSVGForeignObjectElement :: Maybe SVGForeignObjectElement
noSVGForeignObjectElement = Nothing
{-# INLINE noSVGForeignObjectElement #-}
gTypeSVGForeignObjectElement :: JSM GType
gTypeSVGForeignObjectElement = GType . Object <$> jsg "SVGForeignObjectElement"
newtype SVGGElement = SVGGElement { unSVGGElement :: JSVal }
instance PToJSVal SVGGElement where
pToJSVal = unSVGGElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGGElement where
pFromJSVal = SVGGElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGGElement where
toJSVal = return . unSVGGElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGGElement where
fromJSVal v = fmap SVGGElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGGElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGGElement where
makeObject = makeObject . unSVGGElement
instance IsSVGGraphicsElement SVGGElement
instance IsSVGElement SVGGElement
instance IsElement SVGGElement
instance IsNode SVGGElement
instance IsEventTarget SVGGElement
instance IsSlotable SVGGElement
instance IsParentNode SVGGElement
instance IsNonDocumentTypeChildNode SVGGElement
instance IsDocumentAndElementEventHandlers SVGGElement
instance IsChildNode SVGGElement
instance IsAnimatable SVGGElement
instance IsGlobalEventHandlers SVGGElement
instance IsElementCSSInlineStyle SVGGElement
instance IsSVGTests SVGGElement
instance IsSVGExternalResourcesRequired SVGGElement
instance IsGObject SVGGElement where
typeGType _ = gTypeSVGGElement
{-# INLINE typeGType #-}
noSVGGElement :: Maybe SVGGElement
noSVGGElement = Nothing
{-# INLINE noSVGGElement #-}
gTypeSVGGElement :: JSM GType
gTypeSVGGElement = GType . Object <$> jsg "SVGGElement"
newtype SVGGlyphElement = SVGGlyphElement { unSVGGlyphElement :: JSVal }
instance PToJSVal SVGGlyphElement where
pToJSVal = unSVGGlyphElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGGlyphElement where
pFromJSVal = SVGGlyphElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGGlyphElement where
toJSVal = return . unSVGGlyphElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGGlyphElement where
fromJSVal v = fmap SVGGlyphElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGGlyphElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGGlyphElement where
makeObject = makeObject . unSVGGlyphElement
instance IsSVGElement SVGGlyphElement
instance IsElement SVGGlyphElement
instance IsNode SVGGlyphElement
instance IsEventTarget SVGGlyphElement
instance IsSlotable SVGGlyphElement
instance IsParentNode SVGGlyphElement
instance IsNonDocumentTypeChildNode SVGGlyphElement
instance IsDocumentAndElementEventHandlers SVGGlyphElement
instance IsChildNode SVGGlyphElement
instance IsAnimatable SVGGlyphElement
instance IsGlobalEventHandlers SVGGlyphElement
instance IsElementCSSInlineStyle SVGGlyphElement
instance IsGObject SVGGlyphElement where
typeGType _ = gTypeSVGGlyphElement
{-# INLINE typeGType #-}
noSVGGlyphElement :: Maybe SVGGlyphElement
noSVGGlyphElement = Nothing
{-# INLINE noSVGGlyphElement #-}
gTypeSVGGlyphElement :: JSM GType
gTypeSVGGlyphElement = GType . Object <$> jsg "SVGGlyphElement"
newtype SVGGlyphRefElement = SVGGlyphRefElement { unSVGGlyphRefElement :: JSVal }
instance PToJSVal SVGGlyphRefElement where
pToJSVal = unSVGGlyphRefElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGGlyphRefElement where
pFromJSVal = SVGGlyphRefElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGGlyphRefElement where
toJSVal = return . unSVGGlyphRefElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGGlyphRefElement where
fromJSVal v = fmap SVGGlyphRefElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGGlyphRefElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGGlyphRefElement where
makeObject = makeObject . unSVGGlyphRefElement
instance IsSVGElement SVGGlyphRefElement
instance IsElement SVGGlyphRefElement
instance IsNode SVGGlyphRefElement
instance IsEventTarget SVGGlyphRefElement
instance IsSlotable SVGGlyphRefElement
instance IsParentNode SVGGlyphRefElement
instance IsNonDocumentTypeChildNode SVGGlyphRefElement
instance IsDocumentAndElementEventHandlers SVGGlyphRefElement
instance IsChildNode SVGGlyphRefElement
instance IsAnimatable SVGGlyphRefElement
instance IsGlobalEventHandlers SVGGlyphRefElement
instance IsElementCSSInlineStyle SVGGlyphRefElement
instance IsSVGURIReference SVGGlyphRefElement
instance IsGObject SVGGlyphRefElement where
typeGType _ = gTypeSVGGlyphRefElement
{-# INLINE typeGType #-}
noSVGGlyphRefElement :: Maybe SVGGlyphRefElement
noSVGGlyphRefElement = Nothing
{-# INLINE noSVGGlyphRefElement #-}
gTypeSVGGlyphRefElement :: JSM GType
gTypeSVGGlyphRefElement = GType . Object <$> jsg "SVGGlyphRefElement"
newtype SVGGradientElement = SVGGradientElement { unSVGGradientElement :: JSVal }
instance PToJSVal SVGGradientElement where
pToJSVal = unSVGGradientElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGGradientElement where
pFromJSVal = SVGGradientElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGGradientElement where
toJSVal = return . unSVGGradientElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGGradientElement where
fromJSVal v = fmap SVGGradientElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGGradientElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGGradientElement where
makeObject = makeObject . unSVGGradientElement
class (IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsSVGURIReference o, IsSVGExternalResourcesRequired o, IsGObject o) => IsSVGGradientElement o
toSVGGradientElement :: IsSVGGradientElement o => o -> SVGGradientElement
toSVGGradientElement = SVGGradientElement . coerce
instance IsSVGGradientElement SVGGradientElement
instance IsSVGElement SVGGradientElement
instance IsElement SVGGradientElement
instance IsNode SVGGradientElement
instance IsEventTarget SVGGradientElement
instance IsSlotable SVGGradientElement
instance IsParentNode SVGGradientElement
instance IsNonDocumentTypeChildNode SVGGradientElement
instance IsDocumentAndElementEventHandlers SVGGradientElement
instance IsChildNode SVGGradientElement
instance IsAnimatable SVGGradientElement
instance IsGlobalEventHandlers SVGGradientElement
instance IsElementCSSInlineStyle SVGGradientElement
instance IsSVGURIReference SVGGradientElement
instance IsSVGExternalResourcesRequired SVGGradientElement
instance IsGObject SVGGradientElement where
typeGType _ = gTypeSVGGradientElement
{-# INLINE typeGType #-}
noSVGGradientElement :: Maybe SVGGradientElement
noSVGGradientElement = Nothing
{-# INLINE noSVGGradientElement #-}
gTypeSVGGradientElement :: JSM GType
gTypeSVGGradientElement = GType . Object <$> jsg "SVGGradientElement"
newtype SVGGraphicsElement = SVGGraphicsElement { unSVGGraphicsElement :: JSVal }
instance PToJSVal SVGGraphicsElement where
pToJSVal = unSVGGraphicsElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGGraphicsElement where
pFromJSVal = SVGGraphicsElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGGraphicsElement where
toJSVal = return . unSVGGraphicsElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGGraphicsElement where
fromJSVal v = fmap SVGGraphicsElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGGraphicsElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGGraphicsElement where
makeObject = makeObject . unSVGGraphicsElement
class (IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsSVGTests o, IsGObject o) => IsSVGGraphicsElement o
toSVGGraphicsElement :: IsSVGGraphicsElement o => o -> SVGGraphicsElement
toSVGGraphicsElement = SVGGraphicsElement . coerce
instance IsSVGGraphicsElement SVGGraphicsElement
instance IsSVGElement SVGGraphicsElement
instance IsElement SVGGraphicsElement
instance IsNode SVGGraphicsElement
instance IsEventTarget SVGGraphicsElement
instance IsSlotable SVGGraphicsElement
instance IsParentNode SVGGraphicsElement
instance IsNonDocumentTypeChildNode SVGGraphicsElement
instance IsDocumentAndElementEventHandlers SVGGraphicsElement
instance IsChildNode SVGGraphicsElement
instance IsAnimatable SVGGraphicsElement
instance IsGlobalEventHandlers SVGGraphicsElement
instance IsElementCSSInlineStyle SVGGraphicsElement
instance IsSVGTests SVGGraphicsElement
instance IsGObject SVGGraphicsElement where
typeGType _ = gTypeSVGGraphicsElement
{-# INLINE typeGType #-}
noSVGGraphicsElement :: Maybe SVGGraphicsElement
noSVGGraphicsElement = Nothing
{-# INLINE noSVGGraphicsElement #-}
gTypeSVGGraphicsElement :: JSM GType
gTypeSVGGraphicsElement = GType . Object <$> jsg "SVGGraphicsElement"
newtype SVGHKernElement = SVGHKernElement { unSVGHKernElement :: JSVal }
instance PToJSVal SVGHKernElement where
pToJSVal = unSVGHKernElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGHKernElement where
pFromJSVal = SVGHKernElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGHKernElement where
toJSVal = return . unSVGHKernElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGHKernElement where
fromJSVal v = fmap SVGHKernElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGHKernElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGHKernElement where
makeObject = makeObject . unSVGHKernElement
instance IsSVGElement SVGHKernElement
instance IsElement SVGHKernElement
instance IsNode SVGHKernElement
instance IsEventTarget SVGHKernElement
instance IsSlotable SVGHKernElement
instance IsParentNode SVGHKernElement
instance IsNonDocumentTypeChildNode SVGHKernElement
instance IsDocumentAndElementEventHandlers SVGHKernElement
instance IsChildNode SVGHKernElement
instance IsAnimatable SVGHKernElement
instance IsGlobalEventHandlers SVGHKernElement
instance IsElementCSSInlineStyle SVGHKernElement
instance IsGObject SVGHKernElement where
typeGType _ = gTypeSVGHKernElement
{-# INLINE typeGType #-}
noSVGHKernElement :: Maybe SVGHKernElement
noSVGHKernElement = Nothing
{-# INLINE noSVGHKernElement #-}
gTypeSVGHKernElement :: JSM GType
gTypeSVGHKernElement = GType . Object <$> jsg "SVGHKernElement"
newtype SVGImageElement = SVGImageElement { unSVGImageElement :: JSVal }
instance PToJSVal SVGImageElement where
pToJSVal = unSVGImageElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGImageElement where
pFromJSVal = SVGImageElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGImageElement where
toJSVal = return . unSVGImageElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGImageElement where
fromJSVal v = fmap SVGImageElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGImageElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGImageElement where
makeObject = makeObject . unSVGImageElement
instance IsSVGGraphicsElement SVGImageElement
instance IsSVGElement SVGImageElement
instance IsElement SVGImageElement
instance IsNode SVGImageElement
instance IsEventTarget SVGImageElement
instance IsSlotable SVGImageElement
instance IsParentNode SVGImageElement
instance IsNonDocumentTypeChildNode SVGImageElement
instance IsDocumentAndElementEventHandlers SVGImageElement
instance IsChildNode SVGImageElement
instance IsAnimatable SVGImageElement
instance IsGlobalEventHandlers SVGImageElement
instance IsElementCSSInlineStyle SVGImageElement
instance IsSVGTests SVGImageElement
instance IsSVGURIReference SVGImageElement
instance IsSVGExternalResourcesRequired SVGImageElement
instance IsGObject SVGImageElement where
typeGType _ = gTypeSVGImageElement
{-# INLINE typeGType #-}
noSVGImageElement :: Maybe SVGImageElement
noSVGImageElement = Nothing
{-# INLINE noSVGImageElement #-}
gTypeSVGImageElement :: JSM GType
gTypeSVGImageElement = GType . Object <$> jsg "SVGImageElement"
newtype SVGLength = SVGLength { unSVGLength :: JSVal }
instance PToJSVal SVGLength where
pToJSVal = unSVGLength
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGLength where
pFromJSVal = SVGLength
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGLength where
toJSVal = return . unSVGLength
{-# INLINE toJSVal #-}
instance FromJSVal SVGLength where
fromJSVal v = fmap SVGLength <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGLength
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGLength where
makeObject = makeObject . unSVGLength
instance IsGObject SVGLength where
typeGType _ = gTypeSVGLength
{-# INLINE typeGType #-}
noSVGLength :: Maybe SVGLength
noSVGLength = Nothing
{-# INLINE noSVGLength #-}
gTypeSVGLength :: JSM GType
gTypeSVGLength = GType . Object <$> jsg "SVGLength"
newtype SVGLengthList = SVGLengthList { unSVGLengthList :: JSVal }
instance PToJSVal SVGLengthList where
pToJSVal = unSVGLengthList
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGLengthList where
pFromJSVal = SVGLengthList
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGLengthList where
toJSVal = return . unSVGLengthList
{-# INLINE toJSVal #-}
instance FromJSVal SVGLengthList where
fromJSVal v = fmap SVGLengthList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGLengthList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGLengthList where
makeObject = makeObject . unSVGLengthList
instance IsGObject SVGLengthList where
typeGType _ = gTypeSVGLengthList
{-# INLINE typeGType #-}
noSVGLengthList :: Maybe SVGLengthList
noSVGLengthList = Nothing
{-# INLINE noSVGLengthList #-}
gTypeSVGLengthList :: JSM GType
gTypeSVGLengthList = GType . Object <$> jsg "SVGLengthList"
newtype SVGLineElement = SVGLineElement { unSVGLineElement :: JSVal }
instance PToJSVal SVGLineElement where
pToJSVal = unSVGLineElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGLineElement where
pFromJSVal = SVGLineElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGLineElement where
toJSVal = return . unSVGLineElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGLineElement where
fromJSVal v = fmap SVGLineElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGLineElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGLineElement where
makeObject = makeObject . unSVGLineElement
instance IsSVGGraphicsElement SVGLineElement
instance IsSVGElement SVGLineElement
instance IsElement SVGLineElement
instance IsNode SVGLineElement
instance IsEventTarget SVGLineElement
instance IsSlotable SVGLineElement
instance IsParentNode SVGLineElement
instance IsNonDocumentTypeChildNode SVGLineElement
instance IsDocumentAndElementEventHandlers SVGLineElement
instance IsChildNode SVGLineElement
instance IsAnimatable SVGLineElement
instance IsGlobalEventHandlers SVGLineElement
instance IsElementCSSInlineStyle SVGLineElement
instance IsSVGTests SVGLineElement
instance IsSVGExternalResourcesRequired SVGLineElement
instance IsGObject SVGLineElement where
typeGType _ = gTypeSVGLineElement
{-# INLINE typeGType #-}
noSVGLineElement :: Maybe SVGLineElement
noSVGLineElement = Nothing
{-# INLINE noSVGLineElement #-}
gTypeSVGLineElement :: JSM GType
gTypeSVGLineElement = GType . Object <$> jsg "SVGLineElement"
newtype SVGLinearGradientElement = SVGLinearGradientElement { unSVGLinearGradientElement :: JSVal }
instance PToJSVal SVGLinearGradientElement where
pToJSVal = unSVGLinearGradientElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGLinearGradientElement where
pFromJSVal = SVGLinearGradientElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGLinearGradientElement where
toJSVal = return . unSVGLinearGradientElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGLinearGradientElement where
fromJSVal v = fmap SVGLinearGradientElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGLinearGradientElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGLinearGradientElement where
makeObject = makeObject . unSVGLinearGradientElement
instance IsSVGGradientElement SVGLinearGradientElement
instance IsSVGElement SVGLinearGradientElement
instance IsElement SVGLinearGradientElement
instance IsNode SVGLinearGradientElement
instance IsEventTarget SVGLinearGradientElement
instance IsSlotable SVGLinearGradientElement
instance IsParentNode SVGLinearGradientElement
instance IsNonDocumentTypeChildNode SVGLinearGradientElement
instance IsDocumentAndElementEventHandlers SVGLinearGradientElement
instance IsChildNode SVGLinearGradientElement
instance IsAnimatable SVGLinearGradientElement
instance IsGlobalEventHandlers SVGLinearGradientElement
instance IsElementCSSInlineStyle SVGLinearGradientElement
instance IsSVGURIReference SVGLinearGradientElement
instance IsSVGExternalResourcesRequired SVGLinearGradientElement
instance IsGObject SVGLinearGradientElement where
typeGType _ = gTypeSVGLinearGradientElement
{-# INLINE typeGType #-}
noSVGLinearGradientElement :: Maybe SVGLinearGradientElement
noSVGLinearGradientElement = Nothing
{-# INLINE noSVGLinearGradientElement #-}
gTypeSVGLinearGradientElement :: JSM GType
gTypeSVGLinearGradientElement = GType . Object <$> jsg "SVGLinearGradientElement"
newtype SVGMPathElement = SVGMPathElement { unSVGMPathElement :: JSVal }
instance PToJSVal SVGMPathElement where
pToJSVal = unSVGMPathElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGMPathElement where
pFromJSVal = SVGMPathElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGMPathElement where
toJSVal = return . unSVGMPathElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGMPathElement where
fromJSVal v = fmap SVGMPathElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGMPathElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGMPathElement where
makeObject = makeObject . unSVGMPathElement
instance IsSVGElement SVGMPathElement
instance IsElement SVGMPathElement
instance IsNode SVGMPathElement
instance IsEventTarget SVGMPathElement
instance IsSlotable SVGMPathElement
instance IsParentNode SVGMPathElement
instance IsNonDocumentTypeChildNode SVGMPathElement
instance IsDocumentAndElementEventHandlers SVGMPathElement
instance IsChildNode SVGMPathElement
instance IsAnimatable SVGMPathElement
instance IsGlobalEventHandlers SVGMPathElement
instance IsElementCSSInlineStyle SVGMPathElement
instance IsSVGURIReference SVGMPathElement
instance IsSVGExternalResourcesRequired SVGMPathElement
instance IsGObject SVGMPathElement where
typeGType _ = gTypeSVGMPathElement
{-# INLINE typeGType #-}
noSVGMPathElement :: Maybe SVGMPathElement
noSVGMPathElement = Nothing
{-# INLINE noSVGMPathElement #-}
gTypeSVGMPathElement :: JSM GType
gTypeSVGMPathElement = GType . Object <$> jsg "SVGMPathElement"
newtype SVGMarkerElement = SVGMarkerElement { unSVGMarkerElement :: JSVal }
instance PToJSVal SVGMarkerElement where
pToJSVal = unSVGMarkerElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGMarkerElement where
pFromJSVal = SVGMarkerElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGMarkerElement where
toJSVal = return . unSVGMarkerElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGMarkerElement where
fromJSVal v = fmap SVGMarkerElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGMarkerElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGMarkerElement where
makeObject = makeObject . unSVGMarkerElement
instance IsSVGElement SVGMarkerElement
instance IsElement SVGMarkerElement
instance IsNode SVGMarkerElement
instance IsEventTarget SVGMarkerElement
instance IsSlotable SVGMarkerElement
instance IsParentNode SVGMarkerElement
instance IsNonDocumentTypeChildNode SVGMarkerElement
instance IsDocumentAndElementEventHandlers SVGMarkerElement
instance IsChildNode SVGMarkerElement
instance IsAnimatable SVGMarkerElement
instance IsGlobalEventHandlers SVGMarkerElement
instance IsElementCSSInlineStyle SVGMarkerElement
instance IsSVGFitToViewBox SVGMarkerElement
instance IsSVGExternalResourcesRequired SVGMarkerElement
instance IsGObject SVGMarkerElement where
typeGType _ = gTypeSVGMarkerElement
{-# INLINE typeGType #-}
noSVGMarkerElement :: Maybe SVGMarkerElement
noSVGMarkerElement = Nothing
{-# INLINE noSVGMarkerElement #-}
gTypeSVGMarkerElement :: JSM GType
gTypeSVGMarkerElement = GType . Object <$> jsg "SVGMarkerElement"
newtype SVGMaskElement = SVGMaskElement { unSVGMaskElement :: JSVal }
instance PToJSVal SVGMaskElement where
pToJSVal = unSVGMaskElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGMaskElement where
pFromJSVal = SVGMaskElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGMaskElement where
toJSVal = return . unSVGMaskElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGMaskElement where
fromJSVal v = fmap SVGMaskElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGMaskElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGMaskElement where
makeObject = makeObject . unSVGMaskElement
instance IsSVGElement SVGMaskElement
instance IsElement SVGMaskElement
instance IsNode SVGMaskElement
instance IsEventTarget SVGMaskElement
instance IsSlotable SVGMaskElement
instance IsParentNode SVGMaskElement
instance IsNonDocumentTypeChildNode SVGMaskElement
instance IsDocumentAndElementEventHandlers SVGMaskElement
instance IsChildNode SVGMaskElement
instance IsAnimatable SVGMaskElement
instance IsGlobalEventHandlers SVGMaskElement
instance IsElementCSSInlineStyle SVGMaskElement
instance IsSVGTests SVGMaskElement
instance IsSVGExternalResourcesRequired SVGMaskElement
instance IsGObject SVGMaskElement where
typeGType _ = gTypeSVGMaskElement
{-# INLINE typeGType #-}
noSVGMaskElement :: Maybe SVGMaskElement
noSVGMaskElement = Nothing
{-# INLINE noSVGMaskElement #-}
gTypeSVGMaskElement :: JSM GType
gTypeSVGMaskElement = GType . Object <$> jsg "SVGMaskElement"
newtype SVGMatrix = SVGMatrix { unSVGMatrix :: JSVal }
instance PToJSVal SVGMatrix where
pToJSVal = unSVGMatrix
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGMatrix where
pFromJSVal = SVGMatrix
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGMatrix where
toJSVal = return . unSVGMatrix
{-# INLINE toJSVal #-}
instance FromJSVal SVGMatrix where
fromJSVal v = fmap SVGMatrix <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGMatrix
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGMatrix where
makeObject = makeObject . unSVGMatrix
instance IsGObject SVGMatrix where
typeGType _ = gTypeSVGMatrix
{-# INLINE typeGType #-}
noSVGMatrix :: Maybe SVGMatrix
noSVGMatrix = Nothing
{-# INLINE noSVGMatrix #-}
gTypeSVGMatrix :: JSM GType
gTypeSVGMatrix = GType . Object <$> jsg "SVGMatrix"
newtype SVGMetadataElement = SVGMetadataElement { unSVGMetadataElement :: JSVal }
instance PToJSVal SVGMetadataElement where
pToJSVal = unSVGMetadataElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGMetadataElement where
pFromJSVal = SVGMetadataElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGMetadataElement where
toJSVal = return . unSVGMetadataElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGMetadataElement where
fromJSVal v = fmap SVGMetadataElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGMetadataElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGMetadataElement where
makeObject = makeObject . unSVGMetadataElement
instance IsSVGElement SVGMetadataElement
instance IsElement SVGMetadataElement
instance IsNode SVGMetadataElement
instance IsEventTarget SVGMetadataElement
instance IsSlotable SVGMetadataElement
instance IsParentNode SVGMetadataElement
instance IsNonDocumentTypeChildNode SVGMetadataElement
instance IsDocumentAndElementEventHandlers SVGMetadataElement
instance IsChildNode SVGMetadataElement
instance IsAnimatable SVGMetadataElement
instance IsGlobalEventHandlers SVGMetadataElement
instance IsElementCSSInlineStyle SVGMetadataElement
instance IsGObject SVGMetadataElement where
typeGType _ = gTypeSVGMetadataElement
{-# INLINE typeGType #-}
noSVGMetadataElement :: Maybe SVGMetadataElement
noSVGMetadataElement = Nothing
{-# INLINE noSVGMetadataElement #-}
gTypeSVGMetadataElement :: JSM GType
gTypeSVGMetadataElement = GType . Object <$> jsg "SVGMetadataElement"
newtype SVGMissingGlyphElement = SVGMissingGlyphElement { unSVGMissingGlyphElement :: JSVal }
instance PToJSVal SVGMissingGlyphElement where
pToJSVal = unSVGMissingGlyphElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGMissingGlyphElement where
pFromJSVal = SVGMissingGlyphElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGMissingGlyphElement where
toJSVal = return . unSVGMissingGlyphElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGMissingGlyphElement where
fromJSVal v = fmap SVGMissingGlyphElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGMissingGlyphElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGMissingGlyphElement where
makeObject = makeObject . unSVGMissingGlyphElement
instance IsSVGElement SVGMissingGlyphElement
instance IsElement SVGMissingGlyphElement
instance IsNode SVGMissingGlyphElement
instance IsEventTarget SVGMissingGlyphElement
instance IsSlotable SVGMissingGlyphElement
instance IsParentNode SVGMissingGlyphElement
instance IsNonDocumentTypeChildNode SVGMissingGlyphElement
instance IsDocumentAndElementEventHandlers SVGMissingGlyphElement
instance IsChildNode SVGMissingGlyphElement
instance IsAnimatable SVGMissingGlyphElement
instance IsGlobalEventHandlers SVGMissingGlyphElement
instance IsElementCSSInlineStyle SVGMissingGlyphElement
instance IsGObject SVGMissingGlyphElement where
typeGType _ = gTypeSVGMissingGlyphElement
{-# INLINE typeGType #-}
noSVGMissingGlyphElement :: Maybe SVGMissingGlyphElement
noSVGMissingGlyphElement = Nothing
{-# INLINE noSVGMissingGlyphElement #-}
gTypeSVGMissingGlyphElement :: JSM GType
gTypeSVGMissingGlyphElement = GType . Object <$> jsg "SVGMissingGlyphElement"
newtype SVGNumber = SVGNumber { unSVGNumber :: JSVal }
instance PToJSVal SVGNumber where
pToJSVal = unSVGNumber
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGNumber where
pFromJSVal = SVGNumber
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGNumber where
toJSVal = return . unSVGNumber
{-# INLINE toJSVal #-}
instance FromJSVal SVGNumber where
fromJSVal v = fmap SVGNumber <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGNumber
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGNumber where
makeObject = makeObject . unSVGNumber
instance IsGObject SVGNumber where
typeGType _ = gTypeSVGNumber
{-# INLINE typeGType #-}
noSVGNumber :: Maybe SVGNumber
noSVGNumber = Nothing
{-# INLINE noSVGNumber #-}
gTypeSVGNumber :: JSM GType
gTypeSVGNumber = GType . Object <$> jsg "SVGNumber"
newtype SVGNumberList = SVGNumberList { unSVGNumberList :: JSVal }
instance PToJSVal SVGNumberList where
pToJSVal = unSVGNumberList
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGNumberList where
pFromJSVal = SVGNumberList
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGNumberList where
toJSVal = return . unSVGNumberList
{-# INLINE toJSVal #-}
instance FromJSVal SVGNumberList where
fromJSVal v = fmap SVGNumberList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGNumberList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGNumberList where
makeObject = makeObject . unSVGNumberList
instance IsGObject SVGNumberList where
typeGType _ = gTypeSVGNumberList
{-# INLINE typeGType #-}
noSVGNumberList :: Maybe SVGNumberList
noSVGNumberList = Nothing
{-# INLINE noSVGNumberList #-}
gTypeSVGNumberList :: JSM GType
gTypeSVGNumberList = GType . Object <$> jsg "SVGNumberList"
newtype SVGPathElement = SVGPathElement { unSVGPathElement :: JSVal }
instance PToJSVal SVGPathElement where
pToJSVal = unSVGPathElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathElement where
pFromJSVal = SVGPathElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathElement where
toJSVal = return . unSVGPathElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathElement where
fromJSVal v = fmap SVGPathElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathElement where
makeObject = makeObject . unSVGPathElement
instance IsSVGGraphicsElement SVGPathElement
instance IsSVGElement SVGPathElement
instance IsElement SVGPathElement
instance IsNode SVGPathElement
instance IsEventTarget SVGPathElement
instance IsSlotable SVGPathElement
instance IsParentNode SVGPathElement
instance IsNonDocumentTypeChildNode SVGPathElement
instance IsDocumentAndElementEventHandlers SVGPathElement
instance IsChildNode SVGPathElement
instance IsAnimatable SVGPathElement
instance IsGlobalEventHandlers SVGPathElement
instance IsElementCSSInlineStyle SVGPathElement
instance IsSVGTests SVGPathElement
instance IsSVGExternalResourcesRequired SVGPathElement
instance IsGObject SVGPathElement where
typeGType _ = gTypeSVGPathElement
{-# INLINE typeGType #-}
noSVGPathElement :: Maybe SVGPathElement
noSVGPathElement = Nothing
{-# INLINE noSVGPathElement #-}
gTypeSVGPathElement :: JSM GType
gTypeSVGPathElement = GType . Object <$> jsg "SVGPathElement"
newtype SVGPathSeg = SVGPathSeg { unSVGPathSeg :: JSVal }
instance PToJSVal SVGPathSeg where
pToJSVal = unSVGPathSeg
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSeg where
pFromJSVal = SVGPathSeg
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSeg where
toJSVal = return . unSVGPathSeg
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSeg where
fromJSVal v = fmap SVGPathSeg <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSeg
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSeg where
makeObject = makeObject . unSVGPathSeg
class (IsGObject o) => IsSVGPathSeg o
toSVGPathSeg :: IsSVGPathSeg o => o -> SVGPathSeg
toSVGPathSeg = SVGPathSeg . coerce
instance IsSVGPathSeg SVGPathSeg
instance IsGObject SVGPathSeg where
typeGType _ = gTypeSVGPathSeg
{-# INLINE typeGType #-}
noSVGPathSeg :: Maybe SVGPathSeg
noSVGPathSeg = Nothing
{-# INLINE noSVGPathSeg #-}
gTypeSVGPathSeg :: JSM GType
gTypeSVGPathSeg = GType . Object <$> jsg "SVGPathSeg"
newtype SVGPathSegArcAbs = SVGPathSegArcAbs { unSVGPathSegArcAbs :: JSVal }
instance PToJSVal SVGPathSegArcAbs where
pToJSVal = unSVGPathSegArcAbs
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegArcAbs where
pFromJSVal = SVGPathSegArcAbs
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegArcAbs where
toJSVal = return . unSVGPathSegArcAbs
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegArcAbs where
fromJSVal v = fmap SVGPathSegArcAbs <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegArcAbs
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegArcAbs where
makeObject = makeObject . unSVGPathSegArcAbs
instance IsSVGPathSeg SVGPathSegArcAbs
instance IsGObject SVGPathSegArcAbs where
typeGType _ = gTypeSVGPathSegArcAbs
{-# INLINE typeGType #-}
noSVGPathSegArcAbs :: Maybe SVGPathSegArcAbs
noSVGPathSegArcAbs = Nothing
{-# INLINE noSVGPathSegArcAbs #-}
gTypeSVGPathSegArcAbs :: JSM GType
gTypeSVGPathSegArcAbs = GType . Object <$> jsg "SVGPathSegArcAbs"
newtype SVGPathSegArcRel = SVGPathSegArcRel { unSVGPathSegArcRel :: JSVal }
instance PToJSVal SVGPathSegArcRel where
pToJSVal = unSVGPathSegArcRel
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegArcRel where
pFromJSVal = SVGPathSegArcRel
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegArcRel where
toJSVal = return . unSVGPathSegArcRel
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegArcRel where
fromJSVal v = fmap SVGPathSegArcRel <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegArcRel
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegArcRel where
makeObject = makeObject . unSVGPathSegArcRel
instance IsSVGPathSeg SVGPathSegArcRel
instance IsGObject SVGPathSegArcRel where
typeGType _ = gTypeSVGPathSegArcRel
{-# INLINE typeGType #-}
noSVGPathSegArcRel :: Maybe SVGPathSegArcRel
noSVGPathSegArcRel = Nothing
{-# INLINE noSVGPathSegArcRel #-}
gTypeSVGPathSegArcRel :: JSM GType
gTypeSVGPathSegArcRel = GType . Object <$> jsg "SVGPathSegArcRel"
newtype SVGPathSegClosePath = SVGPathSegClosePath { unSVGPathSegClosePath :: JSVal }
instance PToJSVal SVGPathSegClosePath where
pToJSVal = unSVGPathSegClosePath
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegClosePath where
pFromJSVal = SVGPathSegClosePath
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegClosePath where
toJSVal = return . unSVGPathSegClosePath
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegClosePath where
fromJSVal v = fmap SVGPathSegClosePath <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegClosePath
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegClosePath where
makeObject = makeObject . unSVGPathSegClosePath
instance IsSVGPathSeg SVGPathSegClosePath
instance IsGObject SVGPathSegClosePath where
typeGType _ = gTypeSVGPathSegClosePath
{-# INLINE typeGType #-}
noSVGPathSegClosePath :: Maybe SVGPathSegClosePath
noSVGPathSegClosePath = Nothing
{-# INLINE noSVGPathSegClosePath #-}
gTypeSVGPathSegClosePath :: JSM GType
gTypeSVGPathSegClosePath = GType . Object <$> jsg "SVGPathSegClosePath"
newtype SVGPathSegCurvetoCubicAbs = SVGPathSegCurvetoCubicAbs { unSVGPathSegCurvetoCubicAbs :: JSVal }
instance PToJSVal SVGPathSegCurvetoCubicAbs where
pToJSVal = unSVGPathSegCurvetoCubicAbs
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegCurvetoCubicAbs where
pFromJSVal = SVGPathSegCurvetoCubicAbs
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegCurvetoCubicAbs where
toJSVal = return . unSVGPathSegCurvetoCubicAbs
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegCurvetoCubicAbs where
fromJSVal v = fmap SVGPathSegCurvetoCubicAbs <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegCurvetoCubicAbs
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegCurvetoCubicAbs where
makeObject = makeObject . unSVGPathSegCurvetoCubicAbs
instance IsSVGPathSeg SVGPathSegCurvetoCubicAbs
instance IsGObject SVGPathSegCurvetoCubicAbs where
typeGType _ = gTypeSVGPathSegCurvetoCubicAbs
{-# INLINE typeGType #-}
noSVGPathSegCurvetoCubicAbs :: Maybe SVGPathSegCurvetoCubicAbs
noSVGPathSegCurvetoCubicAbs = Nothing
{-# INLINE noSVGPathSegCurvetoCubicAbs #-}
gTypeSVGPathSegCurvetoCubicAbs :: JSM GType
gTypeSVGPathSegCurvetoCubicAbs = GType . Object <$> jsg "SVGPathSegCurvetoCubicAbs"
newtype SVGPathSegCurvetoCubicRel = SVGPathSegCurvetoCubicRel { unSVGPathSegCurvetoCubicRel :: JSVal }
instance PToJSVal SVGPathSegCurvetoCubicRel where
pToJSVal = unSVGPathSegCurvetoCubicRel
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegCurvetoCubicRel where
pFromJSVal = SVGPathSegCurvetoCubicRel
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegCurvetoCubicRel where
toJSVal = return . unSVGPathSegCurvetoCubicRel
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegCurvetoCubicRel where
fromJSVal v = fmap SVGPathSegCurvetoCubicRel <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegCurvetoCubicRel
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegCurvetoCubicRel where
makeObject = makeObject . unSVGPathSegCurvetoCubicRel
instance IsSVGPathSeg SVGPathSegCurvetoCubicRel
instance IsGObject SVGPathSegCurvetoCubicRel where
typeGType _ = gTypeSVGPathSegCurvetoCubicRel
{-# INLINE typeGType #-}
noSVGPathSegCurvetoCubicRel :: Maybe SVGPathSegCurvetoCubicRel
noSVGPathSegCurvetoCubicRel = Nothing
{-# INLINE noSVGPathSegCurvetoCubicRel #-}
gTypeSVGPathSegCurvetoCubicRel :: JSM GType
gTypeSVGPathSegCurvetoCubicRel = GType . Object <$> jsg "SVGPathSegCurvetoCubicRel"
newtype SVGPathSegCurvetoCubicSmoothAbs = SVGPathSegCurvetoCubicSmoothAbs { unSVGPathSegCurvetoCubicSmoothAbs :: JSVal }
instance PToJSVal SVGPathSegCurvetoCubicSmoothAbs where
pToJSVal = unSVGPathSegCurvetoCubicSmoothAbs
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegCurvetoCubicSmoothAbs where
pFromJSVal = SVGPathSegCurvetoCubicSmoothAbs
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegCurvetoCubicSmoothAbs where
toJSVal = return . unSVGPathSegCurvetoCubicSmoothAbs
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegCurvetoCubicSmoothAbs where
fromJSVal v = fmap SVGPathSegCurvetoCubicSmoothAbs <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegCurvetoCubicSmoothAbs
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegCurvetoCubicSmoothAbs where
makeObject = makeObject . unSVGPathSegCurvetoCubicSmoothAbs
instance IsSVGPathSeg SVGPathSegCurvetoCubicSmoothAbs
instance IsGObject SVGPathSegCurvetoCubicSmoothAbs where
typeGType _ = gTypeSVGPathSegCurvetoCubicSmoothAbs
{-# INLINE typeGType #-}
noSVGPathSegCurvetoCubicSmoothAbs :: Maybe SVGPathSegCurvetoCubicSmoothAbs
noSVGPathSegCurvetoCubicSmoothAbs = Nothing
{-# INLINE noSVGPathSegCurvetoCubicSmoothAbs #-}
gTypeSVGPathSegCurvetoCubicSmoothAbs :: JSM GType
gTypeSVGPathSegCurvetoCubicSmoothAbs = GType . Object <$> jsg "SVGPathSegCurvetoCubicSmoothAbs"
newtype SVGPathSegCurvetoCubicSmoothRel = SVGPathSegCurvetoCubicSmoothRel { unSVGPathSegCurvetoCubicSmoothRel :: JSVal }
instance PToJSVal SVGPathSegCurvetoCubicSmoothRel where
pToJSVal = unSVGPathSegCurvetoCubicSmoothRel
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegCurvetoCubicSmoothRel where
pFromJSVal = SVGPathSegCurvetoCubicSmoothRel
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegCurvetoCubicSmoothRel where
toJSVal = return . unSVGPathSegCurvetoCubicSmoothRel
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegCurvetoCubicSmoothRel where
fromJSVal v = fmap SVGPathSegCurvetoCubicSmoothRel <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegCurvetoCubicSmoothRel
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegCurvetoCubicSmoothRel where
makeObject = makeObject . unSVGPathSegCurvetoCubicSmoothRel
instance IsSVGPathSeg SVGPathSegCurvetoCubicSmoothRel
instance IsGObject SVGPathSegCurvetoCubicSmoothRel where
typeGType _ = gTypeSVGPathSegCurvetoCubicSmoothRel
{-# INLINE typeGType #-}
noSVGPathSegCurvetoCubicSmoothRel :: Maybe SVGPathSegCurvetoCubicSmoothRel
noSVGPathSegCurvetoCubicSmoothRel = Nothing
{-# INLINE noSVGPathSegCurvetoCubicSmoothRel #-}
gTypeSVGPathSegCurvetoCubicSmoothRel :: JSM GType
gTypeSVGPathSegCurvetoCubicSmoothRel = GType . Object <$> jsg "SVGPathSegCurvetoCubicSmoothRel"
newtype SVGPathSegCurvetoQuadraticAbs = SVGPathSegCurvetoQuadraticAbs { unSVGPathSegCurvetoQuadraticAbs :: JSVal }
instance PToJSVal SVGPathSegCurvetoQuadraticAbs where
pToJSVal = unSVGPathSegCurvetoQuadraticAbs
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegCurvetoQuadraticAbs where
pFromJSVal = SVGPathSegCurvetoQuadraticAbs
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegCurvetoQuadraticAbs where
toJSVal = return . unSVGPathSegCurvetoQuadraticAbs
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegCurvetoQuadraticAbs where
fromJSVal v = fmap SVGPathSegCurvetoQuadraticAbs <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegCurvetoQuadraticAbs
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegCurvetoQuadraticAbs where
makeObject = makeObject . unSVGPathSegCurvetoQuadraticAbs
instance IsSVGPathSeg SVGPathSegCurvetoQuadraticAbs
instance IsGObject SVGPathSegCurvetoQuadraticAbs where
typeGType _ = gTypeSVGPathSegCurvetoQuadraticAbs
{-# INLINE typeGType #-}
noSVGPathSegCurvetoQuadraticAbs :: Maybe SVGPathSegCurvetoQuadraticAbs
noSVGPathSegCurvetoQuadraticAbs = Nothing
{-# INLINE noSVGPathSegCurvetoQuadraticAbs #-}
gTypeSVGPathSegCurvetoQuadraticAbs :: JSM GType
gTypeSVGPathSegCurvetoQuadraticAbs = GType . Object <$> jsg "SVGPathSegCurvetoQuadraticAbs"
newtype SVGPathSegCurvetoQuadraticRel = SVGPathSegCurvetoQuadraticRel { unSVGPathSegCurvetoQuadraticRel :: JSVal }
instance PToJSVal SVGPathSegCurvetoQuadraticRel where
pToJSVal = unSVGPathSegCurvetoQuadraticRel
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegCurvetoQuadraticRel where
pFromJSVal = SVGPathSegCurvetoQuadraticRel
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegCurvetoQuadraticRel where
toJSVal = return . unSVGPathSegCurvetoQuadraticRel
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegCurvetoQuadraticRel where
fromJSVal v = fmap SVGPathSegCurvetoQuadraticRel <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegCurvetoQuadraticRel
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegCurvetoQuadraticRel where
makeObject = makeObject . unSVGPathSegCurvetoQuadraticRel
instance IsSVGPathSeg SVGPathSegCurvetoQuadraticRel
instance IsGObject SVGPathSegCurvetoQuadraticRel where
typeGType _ = gTypeSVGPathSegCurvetoQuadraticRel
{-# INLINE typeGType #-}
noSVGPathSegCurvetoQuadraticRel :: Maybe SVGPathSegCurvetoQuadraticRel
noSVGPathSegCurvetoQuadraticRel = Nothing
{-# INLINE noSVGPathSegCurvetoQuadraticRel #-}
gTypeSVGPathSegCurvetoQuadraticRel :: JSM GType
gTypeSVGPathSegCurvetoQuadraticRel = GType . Object <$> jsg "SVGPathSegCurvetoQuadraticRel"
newtype SVGPathSegCurvetoQuadraticSmoothAbs = SVGPathSegCurvetoQuadraticSmoothAbs { unSVGPathSegCurvetoQuadraticSmoothAbs :: JSVal }
instance PToJSVal SVGPathSegCurvetoQuadraticSmoothAbs where
pToJSVal = unSVGPathSegCurvetoQuadraticSmoothAbs
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegCurvetoQuadraticSmoothAbs where
pFromJSVal = SVGPathSegCurvetoQuadraticSmoothAbs
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegCurvetoQuadraticSmoothAbs where
toJSVal = return . unSVGPathSegCurvetoQuadraticSmoothAbs
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegCurvetoQuadraticSmoothAbs where
fromJSVal v = fmap SVGPathSegCurvetoQuadraticSmoothAbs <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegCurvetoQuadraticSmoothAbs
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegCurvetoQuadraticSmoothAbs where
makeObject = makeObject . unSVGPathSegCurvetoQuadraticSmoothAbs
instance IsSVGPathSeg SVGPathSegCurvetoQuadraticSmoothAbs
instance IsGObject SVGPathSegCurvetoQuadraticSmoothAbs where
typeGType _ = gTypeSVGPathSegCurvetoQuadraticSmoothAbs
{-# INLINE typeGType #-}
noSVGPathSegCurvetoQuadraticSmoothAbs :: Maybe SVGPathSegCurvetoQuadraticSmoothAbs
noSVGPathSegCurvetoQuadraticSmoothAbs = Nothing
{-# INLINE noSVGPathSegCurvetoQuadraticSmoothAbs #-}
gTypeSVGPathSegCurvetoQuadraticSmoothAbs :: JSM GType
gTypeSVGPathSegCurvetoQuadraticSmoothAbs = GType . Object <$> jsg "SVGPathSegCurvetoQuadraticSmoothAbs"
newtype SVGPathSegCurvetoQuadraticSmoothRel = SVGPathSegCurvetoQuadraticSmoothRel { unSVGPathSegCurvetoQuadraticSmoothRel :: JSVal }
instance PToJSVal SVGPathSegCurvetoQuadraticSmoothRel where
pToJSVal = unSVGPathSegCurvetoQuadraticSmoothRel
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegCurvetoQuadraticSmoothRel where
pFromJSVal = SVGPathSegCurvetoQuadraticSmoothRel
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegCurvetoQuadraticSmoothRel where
toJSVal = return . unSVGPathSegCurvetoQuadraticSmoothRel
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegCurvetoQuadraticSmoothRel where
fromJSVal v = fmap SVGPathSegCurvetoQuadraticSmoothRel <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegCurvetoQuadraticSmoothRel
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegCurvetoQuadraticSmoothRel where
makeObject = makeObject . unSVGPathSegCurvetoQuadraticSmoothRel
instance IsSVGPathSeg SVGPathSegCurvetoQuadraticSmoothRel
instance IsGObject SVGPathSegCurvetoQuadraticSmoothRel where
typeGType _ = gTypeSVGPathSegCurvetoQuadraticSmoothRel
{-# INLINE typeGType #-}
noSVGPathSegCurvetoQuadraticSmoothRel :: Maybe SVGPathSegCurvetoQuadraticSmoothRel
noSVGPathSegCurvetoQuadraticSmoothRel = Nothing
{-# INLINE noSVGPathSegCurvetoQuadraticSmoothRel #-}
gTypeSVGPathSegCurvetoQuadraticSmoothRel :: JSM GType
gTypeSVGPathSegCurvetoQuadraticSmoothRel = GType . Object <$> jsg "SVGPathSegCurvetoQuadraticSmoothRel"
newtype SVGPathSegLinetoAbs = SVGPathSegLinetoAbs { unSVGPathSegLinetoAbs :: JSVal }
instance PToJSVal SVGPathSegLinetoAbs where
pToJSVal = unSVGPathSegLinetoAbs
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegLinetoAbs where
pFromJSVal = SVGPathSegLinetoAbs
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegLinetoAbs where
toJSVal = return . unSVGPathSegLinetoAbs
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegLinetoAbs where
fromJSVal v = fmap SVGPathSegLinetoAbs <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegLinetoAbs
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegLinetoAbs where
makeObject = makeObject . unSVGPathSegLinetoAbs
instance IsSVGPathSeg SVGPathSegLinetoAbs
instance IsGObject SVGPathSegLinetoAbs where
typeGType _ = gTypeSVGPathSegLinetoAbs
{-# INLINE typeGType #-}
noSVGPathSegLinetoAbs :: Maybe SVGPathSegLinetoAbs
noSVGPathSegLinetoAbs = Nothing
{-# INLINE noSVGPathSegLinetoAbs #-}
gTypeSVGPathSegLinetoAbs :: JSM GType
gTypeSVGPathSegLinetoAbs = GType . Object <$> jsg "SVGPathSegLinetoAbs"
newtype SVGPathSegLinetoHorizontalAbs = SVGPathSegLinetoHorizontalAbs { unSVGPathSegLinetoHorizontalAbs :: JSVal }
instance PToJSVal SVGPathSegLinetoHorizontalAbs where
pToJSVal = unSVGPathSegLinetoHorizontalAbs
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegLinetoHorizontalAbs where
pFromJSVal = SVGPathSegLinetoHorizontalAbs
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegLinetoHorizontalAbs where
toJSVal = return . unSVGPathSegLinetoHorizontalAbs
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegLinetoHorizontalAbs where
fromJSVal v = fmap SVGPathSegLinetoHorizontalAbs <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegLinetoHorizontalAbs
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegLinetoHorizontalAbs where
makeObject = makeObject . unSVGPathSegLinetoHorizontalAbs
instance IsSVGPathSeg SVGPathSegLinetoHorizontalAbs
instance IsGObject SVGPathSegLinetoHorizontalAbs where
typeGType _ = gTypeSVGPathSegLinetoHorizontalAbs
{-# INLINE typeGType #-}
noSVGPathSegLinetoHorizontalAbs :: Maybe SVGPathSegLinetoHorizontalAbs
noSVGPathSegLinetoHorizontalAbs = Nothing
{-# INLINE noSVGPathSegLinetoHorizontalAbs #-}
gTypeSVGPathSegLinetoHorizontalAbs :: JSM GType
gTypeSVGPathSegLinetoHorizontalAbs = GType . Object <$> jsg "SVGPathSegLinetoHorizontalAbs"
newtype SVGPathSegLinetoHorizontalRel = SVGPathSegLinetoHorizontalRel { unSVGPathSegLinetoHorizontalRel :: JSVal }
instance PToJSVal SVGPathSegLinetoHorizontalRel where
pToJSVal = unSVGPathSegLinetoHorizontalRel
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegLinetoHorizontalRel where
pFromJSVal = SVGPathSegLinetoHorizontalRel
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegLinetoHorizontalRel where
toJSVal = return . unSVGPathSegLinetoHorizontalRel
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegLinetoHorizontalRel where
fromJSVal v = fmap SVGPathSegLinetoHorizontalRel <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegLinetoHorizontalRel
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegLinetoHorizontalRel where
makeObject = makeObject . unSVGPathSegLinetoHorizontalRel
instance IsSVGPathSeg SVGPathSegLinetoHorizontalRel
instance IsGObject SVGPathSegLinetoHorizontalRel where
typeGType _ = gTypeSVGPathSegLinetoHorizontalRel
{-# INLINE typeGType #-}
noSVGPathSegLinetoHorizontalRel :: Maybe SVGPathSegLinetoHorizontalRel
noSVGPathSegLinetoHorizontalRel = Nothing
{-# INLINE noSVGPathSegLinetoHorizontalRel #-}
gTypeSVGPathSegLinetoHorizontalRel :: JSM GType
gTypeSVGPathSegLinetoHorizontalRel = GType . Object <$> jsg "SVGPathSegLinetoHorizontalRel"
newtype SVGPathSegLinetoRel = SVGPathSegLinetoRel { unSVGPathSegLinetoRel :: JSVal }
instance PToJSVal SVGPathSegLinetoRel where
pToJSVal = unSVGPathSegLinetoRel
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegLinetoRel where
pFromJSVal = SVGPathSegLinetoRel
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegLinetoRel where
toJSVal = return . unSVGPathSegLinetoRel
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegLinetoRel where
fromJSVal v = fmap SVGPathSegLinetoRel <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegLinetoRel
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegLinetoRel where
makeObject = makeObject . unSVGPathSegLinetoRel
instance IsSVGPathSeg SVGPathSegLinetoRel
instance IsGObject SVGPathSegLinetoRel where
typeGType _ = gTypeSVGPathSegLinetoRel
{-# INLINE typeGType #-}
noSVGPathSegLinetoRel :: Maybe SVGPathSegLinetoRel
noSVGPathSegLinetoRel = Nothing
{-# INLINE noSVGPathSegLinetoRel #-}
gTypeSVGPathSegLinetoRel :: JSM GType
gTypeSVGPathSegLinetoRel = GType . Object <$> jsg "SVGPathSegLinetoRel"
newtype SVGPathSegLinetoVerticalAbs = SVGPathSegLinetoVerticalAbs { unSVGPathSegLinetoVerticalAbs :: JSVal }
instance PToJSVal SVGPathSegLinetoVerticalAbs where
pToJSVal = unSVGPathSegLinetoVerticalAbs
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegLinetoVerticalAbs where
pFromJSVal = SVGPathSegLinetoVerticalAbs
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegLinetoVerticalAbs where
toJSVal = return . unSVGPathSegLinetoVerticalAbs
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegLinetoVerticalAbs where
fromJSVal v = fmap SVGPathSegLinetoVerticalAbs <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegLinetoVerticalAbs
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegLinetoVerticalAbs where
makeObject = makeObject . unSVGPathSegLinetoVerticalAbs
instance IsSVGPathSeg SVGPathSegLinetoVerticalAbs
instance IsGObject SVGPathSegLinetoVerticalAbs where
typeGType _ = gTypeSVGPathSegLinetoVerticalAbs
{-# INLINE typeGType #-}
noSVGPathSegLinetoVerticalAbs :: Maybe SVGPathSegLinetoVerticalAbs
noSVGPathSegLinetoVerticalAbs = Nothing
{-# INLINE noSVGPathSegLinetoVerticalAbs #-}
gTypeSVGPathSegLinetoVerticalAbs :: JSM GType
gTypeSVGPathSegLinetoVerticalAbs = GType . Object <$> jsg "SVGPathSegLinetoVerticalAbs"
newtype SVGPathSegLinetoVerticalRel = SVGPathSegLinetoVerticalRel { unSVGPathSegLinetoVerticalRel :: JSVal }
instance PToJSVal SVGPathSegLinetoVerticalRel where
pToJSVal = unSVGPathSegLinetoVerticalRel
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegLinetoVerticalRel where
pFromJSVal = SVGPathSegLinetoVerticalRel
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegLinetoVerticalRel where
toJSVal = return . unSVGPathSegLinetoVerticalRel
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegLinetoVerticalRel where
fromJSVal v = fmap SVGPathSegLinetoVerticalRel <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegLinetoVerticalRel
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegLinetoVerticalRel where
makeObject = makeObject . unSVGPathSegLinetoVerticalRel
instance IsSVGPathSeg SVGPathSegLinetoVerticalRel
instance IsGObject SVGPathSegLinetoVerticalRel where
typeGType _ = gTypeSVGPathSegLinetoVerticalRel
{-# INLINE typeGType #-}
noSVGPathSegLinetoVerticalRel :: Maybe SVGPathSegLinetoVerticalRel
noSVGPathSegLinetoVerticalRel = Nothing
{-# INLINE noSVGPathSegLinetoVerticalRel #-}
gTypeSVGPathSegLinetoVerticalRel :: JSM GType
gTypeSVGPathSegLinetoVerticalRel = GType . Object <$> jsg "SVGPathSegLinetoVerticalRel"
newtype SVGPathSegList = SVGPathSegList { unSVGPathSegList :: JSVal }
instance PToJSVal SVGPathSegList where
pToJSVal = unSVGPathSegList
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegList where
pFromJSVal = SVGPathSegList
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegList where
toJSVal = return . unSVGPathSegList
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegList where
fromJSVal v = fmap SVGPathSegList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegList where
makeObject = makeObject . unSVGPathSegList
instance IsGObject SVGPathSegList where
typeGType _ = gTypeSVGPathSegList
{-# INLINE typeGType #-}
noSVGPathSegList :: Maybe SVGPathSegList
noSVGPathSegList = Nothing
{-# INLINE noSVGPathSegList #-}
gTypeSVGPathSegList :: JSM GType
gTypeSVGPathSegList = GType . Object <$> jsg "SVGPathSegList"
newtype SVGPathSegMovetoAbs = SVGPathSegMovetoAbs { unSVGPathSegMovetoAbs :: JSVal }
instance PToJSVal SVGPathSegMovetoAbs where
pToJSVal = unSVGPathSegMovetoAbs
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegMovetoAbs where
pFromJSVal = SVGPathSegMovetoAbs
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegMovetoAbs where
toJSVal = return . unSVGPathSegMovetoAbs
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegMovetoAbs where
fromJSVal v = fmap SVGPathSegMovetoAbs <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegMovetoAbs
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegMovetoAbs where
makeObject = makeObject . unSVGPathSegMovetoAbs
instance IsSVGPathSeg SVGPathSegMovetoAbs
instance IsGObject SVGPathSegMovetoAbs where
typeGType _ = gTypeSVGPathSegMovetoAbs
{-# INLINE typeGType #-}
noSVGPathSegMovetoAbs :: Maybe SVGPathSegMovetoAbs
noSVGPathSegMovetoAbs = Nothing
{-# INLINE noSVGPathSegMovetoAbs #-}
gTypeSVGPathSegMovetoAbs :: JSM GType
gTypeSVGPathSegMovetoAbs = GType . Object <$> jsg "SVGPathSegMovetoAbs"
newtype SVGPathSegMovetoRel = SVGPathSegMovetoRel { unSVGPathSegMovetoRel :: JSVal }
instance PToJSVal SVGPathSegMovetoRel where
pToJSVal = unSVGPathSegMovetoRel
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPathSegMovetoRel where
pFromJSVal = SVGPathSegMovetoRel
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPathSegMovetoRel where
toJSVal = return . unSVGPathSegMovetoRel
{-# INLINE toJSVal #-}
instance FromJSVal SVGPathSegMovetoRel where
fromJSVal v = fmap SVGPathSegMovetoRel <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPathSegMovetoRel
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPathSegMovetoRel where
makeObject = makeObject . unSVGPathSegMovetoRel
instance IsSVGPathSeg SVGPathSegMovetoRel
instance IsGObject SVGPathSegMovetoRel where
typeGType _ = gTypeSVGPathSegMovetoRel
{-# INLINE typeGType #-}
noSVGPathSegMovetoRel :: Maybe SVGPathSegMovetoRel
noSVGPathSegMovetoRel = Nothing
{-# INLINE noSVGPathSegMovetoRel #-}
gTypeSVGPathSegMovetoRel :: JSM GType
gTypeSVGPathSegMovetoRel = GType . Object <$> jsg "SVGPathSegMovetoRel"
newtype SVGPatternElement = SVGPatternElement { unSVGPatternElement :: JSVal }
instance PToJSVal SVGPatternElement where
pToJSVal = unSVGPatternElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPatternElement where
pFromJSVal = SVGPatternElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPatternElement where
toJSVal = return . unSVGPatternElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGPatternElement where
fromJSVal v = fmap SVGPatternElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPatternElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPatternElement where
makeObject = makeObject . unSVGPatternElement
instance IsSVGElement SVGPatternElement
instance IsElement SVGPatternElement
instance IsNode SVGPatternElement
instance IsEventTarget SVGPatternElement
instance IsSlotable SVGPatternElement
instance IsParentNode SVGPatternElement
instance IsNonDocumentTypeChildNode SVGPatternElement
instance IsDocumentAndElementEventHandlers SVGPatternElement
instance IsChildNode SVGPatternElement
instance IsAnimatable SVGPatternElement
instance IsGlobalEventHandlers SVGPatternElement
instance IsElementCSSInlineStyle SVGPatternElement
instance IsSVGURIReference SVGPatternElement
instance IsSVGTests SVGPatternElement
instance IsSVGFitToViewBox SVGPatternElement
instance IsSVGExternalResourcesRequired SVGPatternElement
instance IsGObject SVGPatternElement where
typeGType _ = gTypeSVGPatternElement
{-# INLINE typeGType #-}
noSVGPatternElement :: Maybe SVGPatternElement
noSVGPatternElement = Nothing
{-# INLINE noSVGPatternElement #-}
gTypeSVGPatternElement :: JSM GType
gTypeSVGPatternElement = GType . Object <$> jsg "SVGPatternElement"
newtype SVGPoint = SVGPoint { unSVGPoint :: JSVal }
instance PToJSVal SVGPoint where
pToJSVal = unSVGPoint
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPoint where
pFromJSVal = SVGPoint
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPoint where
toJSVal = return . unSVGPoint
{-# INLINE toJSVal #-}
instance FromJSVal SVGPoint where
fromJSVal v = fmap SVGPoint <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPoint
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPoint where
makeObject = makeObject . unSVGPoint
instance IsGObject SVGPoint where
typeGType _ = gTypeSVGPoint
{-# INLINE typeGType #-}
noSVGPoint :: Maybe SVGPoint
noSVGPoint = Nothing
{-# INLINE noSVGPoint #-}
gTypeSVGPoint :: JSM GType
gTypeSVGPoint = GType . Object <$> jsg "SVGPoint"
newtype SVGPointList = SVGPointList { unSVGPointList :: JSVal }
instance PToJSVal SVGPointList where
pToJSVal = unSVGPointList
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPointList where
pFromJSVal = SVGPointList
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPointList where
toJSVal = return . unSVGPointList
{-# INLINE toJSVal #-}
instance FromJSVal SVGPointList where
fromJSVal v = fmap SVGPointList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPointList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPointList where
makeObject = makeObject . unSVGPointList
instance IsGObject SVGPointList where
typeGType _ = gTypeSVGPointList
{-# INLINE typeGType #-}
noSVGPointList :: Maybe SVGPointList
noSVGPointList = Nothing
{-# INLINE noSVGPointList #-}
gTypeSVGPointList :: JSM GType
gTypeSVGPointList = GType . Object <$> jsg "SVGPointList"
newtype SVGPolygonElement = SVGPolygonElement { unSVGPolygonElement :: JSVal }
instance PToJSVal SVGPolygonElement where
pToJSVal = unSVGPolygonElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPolygonElement where
pFromJSVal = SVGPolygonElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPolygonElement where
toJSVal = return . unSVGPolygonElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGPolygonElement where
fromJSVal v = fmap SVGPolygonElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPolygonElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPolygonElement where
makeObject = makeObject . unSVGPolygonElement
instance IsSVGGraphicsElement SVGPolygonElement
instance IsSVGElement SVGPolygonElement
instance IsElement SVGPolygonElement
instance IsNode SVGPolygonElement
instance IsEventTarget SVGPolygonElement
instance IsSlotable SVGPolygonElement
instance IsParentNode SVGPolygonElement
instance IsNonDocumentTypeChildNode SVGPolygonElement
instance IsDocumentAndElementEventHandlers SVGPolygonElement
instance IsChildNode SVGPolygonElement
instance IsAnimatable SVGPolygonElement
instance IsGlobalEventHandlers SVGPolygonElement
instance IsElementCSSInlineStyle SVGPolygonElement
instance IsSVGTests SVGPolygonElement
instance IsSVGExternalResourcesRequired SVGPolygonElement
instance IsGObject SVGPolygonElement where
typeGType _ = gTypeSVGPolygonElement
{-# INLINE typeGType #-}
noSVGPolygonElement :: Maybe SVGPolygonElement
noSVGPolygonElement = Nothing
{-# INLINE noSVGPolygonElement #-}
gTypeSVGPolygonElement :: JSM GType
gTypeSVGPolygonElement = GType . Object <$> jsg "SVGPolygonElement"
newtype SVGPolylineElement = SVGPolylineElement { unSVGPolylineElement :: JSVal }
instance PToJSVal SVGPolylineElement where
pToJSVal = unSVGPolylineElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPolylineElement where
pFromJSVal = SVGPolylineElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPolylineElement where
toJSVal = return . unSVGPolylineElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGPolylineElement where
fromJSVal v = fmap SVGPolylineElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPolylineElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPolylineElement where
makeObject = makeObject . unSVGPolylineElement
instance IsSVGGraphicsElement SVGPolylineElement
instance IsSVGElement SVGPolylineElement
instance IsElement SVGPolylineElement
instance IsNode SVGPolylineElement
instance IsEventTarget SVGPolylineElement
instance IsSlotable SVGPolylineElement
instance IsParentNode SVGPolylineElement
instance IsNonDocumentTypeChildNode SVGPolylineElement
instance IsDocumentAndElementEventHandlers SVGPolylineElement
instance IsChildNode SVGPolylineElement
instance IsAnimatable SVGPolylineElement
instance IsGlobalEventHandlers SVGPolylineElement
instance IsElementCSSInlineStyle SVGPolylineElement
instance IsSVGTests SVGPolylineElement
instance IsSVGExternalResourcesRequired SVGPolylineElement
instance IsGObject SVGPolylineElement where
typeGType _ = gTypeSVGPolylineElement
{-# INLINE typeGType #-}
noSVGPolylineElement :: Maybe SVGPolylineElement
noSVGPolylineElement = Nothing
{-# INLINE noSVGPolylineElement #-}
gTypeSVGPolylineElement :: JSM GType
gTypeSVGPolylineElement = GType . Object <$> jsg "SVGPolylineElement"
newtype SVGPreserveAspectRatio = SVGPreserveAspectRatio { unSVGPreserveAspectRatio :: JSVal }
instance PToJSVal SVGPreserveAspectRatio where
pToJSVal = unSVGPreserveAspectRatio
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGPreserveAspectRatio where
pFromJSVal = SVGPreserveAspectRatio
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGPreserveAspectRatio where
toJSVal = return . unSVGPreserveAspectRatio
{-# INLINE toJSVal #-}
instance FromJSVal SVGPreserveAspectRatio where
fromJSVal v = fmap SVGPreserveAspectRatio <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGPreserveAspectRatio
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGPreserveAspectRatio where
makeObject = makeObject . unSVGPreserveAspectRatio
instance IsGObject SVGPreserveAspectRatio where
typeGType _ = gTypeSVGPreserveAspectRatio
{-# INLINE typeGType #-}
noSVGPreserveAspectRatio :: Maybe SVGPreserveAspectRatio
noSVGPreserveAspectRatio = Nothing
{-# INLINE noSVGPreserveAspectRatio #-}
gTypeSVGPreserveAspectRatio :: JSM GType
gTypeSVGPreserveAspectRatio = GType . Object <$> jsg "SVGPreserveAspectRatio"
newtype SVGRadialGradientElement = SVGRadialGradientElement { unSVGRadialGradientElement :: JSVal }
instance PToJSVal SVGRadialGradientElement where
pToJSVal = unSVGRadialGradientElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGRadialGradientElement where
pFromJSVal = SVGRadialGradientElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGRadialGradientElement where
toJSVal = return . unSVGRadialGradientElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGRadialGradientElement where
fromJSVal v = fmap SVGRadialGradientElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGRadialGradientElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGRadialGradientElement where
makeObject = makeObject . unSVGRadialGradientElement
instance IsSVGGradientElement SVGRadialGradientElement
instance IsSVGElement SVGRadialGradientElement
instance IsElement SVGRadialGradientElement
instance IsNode SVGRadialGradientElement
instance IsEventTarget SVGRadialGradientElement
instance IsSlotable SVGRadialGradientElement
instance IsParentNode SVGRadialGradientElement
instance IsNonDocumentTypeChildNode SVGRadialGradientElement
instance IsDocumentAndElementEventHandlers SVGRadialGradientElement
instance IsChildNode SVGRadialGradientElement
instance IsAnimatable SVGRadialGradientElement
instance IsGlobalEventHandlers SVGRadialGradientElement
instance IsElementCSSInlineStyle SVGRadialGradientElement
instance IsSVGURIReference SVGRadialGradientElement
instance IsSVGExternalResourcesRequired SVGRadialGradientElement
instance IsGObject SVGRadialGradientElement where
typeGType _ = gTypeSVGRadialGradientElement
{-# INLINE typeGType #-}
noSVGRadialGradientElement :: Maybe SVGRadialGradientElement
noSVGRadialGradientElement = Nothing
{-# INLINE noSVGRadialGradientElement #-}
gTypeSVGRadialGradientElement :: JSM GType
gTypeSVGRadialGradientElement = GType . Object <$> jsg "SVGRadialGradientElement"
newtype SVGRect = SVGRect { unSVGRect :: JSVal }
instance PToJSVal SVGRect where
pToJSVal = unSVGRect
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGRect where
pFromJSVal = SVGRect
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGRect where
toJSVal = return . unSVGRect
{-# INLINE toJSVal #-}
instance FromJSVal SVGRect where
fromJSVal v = fmap SVGRect <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGRect
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGRect where
makeObject = makeObject . unSVGRect
instance IsGObject SVGRect where
typeGType _ = gTypeSVGRect
{-# INLINE typeGType #-}
noSVGRect :: Maybe SVGRect
noSVGRect = Nothing
{-# INLINE noSVGRect #-}
gTypeSVGRect :: JSM GType
gTypeSVGRect = GType . Object <$> jsg "SVGRect"
newtype SVGRectElement = SVGRectElement { unSVGRectElement :: JSVal }
instance PToJSVal SVGRectElement where
pToJSVal = unSVGRectElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGRectElement where
pFromJSVal = SVGRectElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGRectElement where
toJSVal = return . unSVGRectElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGRectElement where
fromJSVal v = fmap SVGRectElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGRectElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGRectElement where
makeObject = makeObject . unSVGRectElement
instance IsSVGGraphicsElement SVGRectElement
instance IsSVGElement SVGRectElement
instance IsElement SVGRectElement
instance IsNode SVGRectElement
instance IsEventTarget SVGRectElement
instance IsSlotable SVGRectElement
instance IsParentNode SVGRectElement
instance IsNonDocumentTypeChildNode SVGRectElement
instance IsDocumentAndElementEventHandlers SVGRectElement
instance IsChildNode SVGRectElement
instance IsAnimatable SVGRectElement
instance IsGlobalEventHandlers SVGRectElement
instance IsElementCSSInlineStyle SVGRectElement
instance IsSVGTests SVGRectElement
instance IsSVGExternalResourcesRequired SVGRectElement
instance IsGObject SVGRectElement where
typeGType _ = gTypeSVGRectElement
{-# INLINE typeGType #-}
noSVGRectElement :: Maybe SVGRectElement
noSVGRectElement = Nothing
{-# INLINE noSVGRectElement #-}
gTypeSVGRectElement :: JSM GType
gTypeSVGRectElement = GType . Object <$> jsg "SVGRectElement"
newtype SVGRenderingIntent = SVGRenderingIntent { unSVGRenderingIntent :: JSVal }
instance PToJSVal SVGRenderingIntent where
pToJSVal = unSVGRenderingIntent
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGRenderingIntent where
pFromJSVal = SVGRenderingIntent
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGRenderingIntent where
toJSVal = return . unSVGRenderingIntent
{-# INLINE toJSVal #-}
instance FromJSVal SVGRenderingIntent where
fromJSVal v = fmap SVGRenderingIntent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGRenderingIntent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGRenderingIntent where
makeObject = makeObject . unSVGRenderingIntent
instance IsGObject SVGRenderingIntent where
typeGType _ = gTypeSVGRenderingIntent
{-# INLINE typeGType #-}
noSVGRenderingIntent :: Maybe SVGRenderingIntent
noSVGRenderingIntent = Nothing
{-# INLINE noSVGRenderingIntent #-}
gTypeSVGRenderingIntent :: JSM GType
gTypeSVGRenderingIntent = GType . Object <$> jsg "SVGRenderingIntent"
newtype SVGSVGElement = SVGSVGElement { unSVGSVGElement :: JSVal }
instance PToJSVal SVGSVGElement where
pToJSVal = unSVGSVGElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGSVGElement where
pFromJSVal = SVGSVGElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGSVGElement where
toJSVal = return . unSVGSVGElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGSVGElement where
fromJSVal v = fmap SVGSVGElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGSVGElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGSVGElement where
makeObject = makeObject . unSVGSVGElement
instance IsSVGGraphicsElement SVGSVGElement
instance IsSVGElement SVGSVGElement
instance IsElement SVGSVGElement
instance IsNode SVGSVGElement
instance IsEventTarget SVGSVGElement
instance IsSlotable SVGSVGElement
instance IsParentNode SVGSVGElement
instance IsNonDocumentTypeChildNode SVGSVGElement
instance IsDocumentAndElementEventHandlers SVGSVGElement
instance IsChildNode SVGSVGElement
instance IsAnimatable SVGSVGElement
instance IsGlobalEventHandlers SVGSVGElement
instance IsElementCSSInlineStyle SVGSVGElement
instance IsSVGTests SVGSVGElement
instance IsSVGZoomAndPan SVGSVGElement
instance IsSVGFitToViewBox SVGSVGElement
instance IsSVGExternalResourcesRequired SVGSVGElement
instance IsGObject SVGSVGElement where
typeGType _ = gTypeSVGSVGElement
{-# INLINE typeGType #-}
noSVGSVGElement :: Maybe SVGSVGElement
noSVGSVGElement = Nothing
{-# INLINE noSVGSVGElement #-}
gTypeSVGSVGElement :: JSM GType
gTypeSVGSVGElement = GType . Object <$> jsg "SVGSVGElement"
newtype SVGScriptElement = SVGScriptElement { unSVGScriptElement :: JSVal }
instance PToJSVal SVGScriptElement where
pToJSVal = unSVGScriptElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGScriptElement where
pFromJSVal = SVGScriptElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGScriptElement where
toJSVal = return . unSVGScriptElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGScriptElement where
fromJSVal v = fmap SVGScriptElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGScriptElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGScriptElement where
makeObject = makeObject . unSVGScriptElement
instance IsSVGElement SVGScriptElement
instance IsElement SVGScriptElement
instance IsNode SVGScriptElement
instance IsEventTarget SVGScriptElement
instance IsSlotable SVGScriptElement
instance IsParentNode SVGScriptElement
instance IsNonDocumentTypeChildNode SVGScriptElement
instance IsDocumentAndElementEventHandlers SVGScriptElement
instance IsChildNode SVGScriptElement
instance IsAnimatable SVGScriptElement
instance IsGlobalEventHandlers SVGScriptElement
instance IsElementCSSInlineStyle SVGScriptElement
instance IsSVGURIReference SVGScriptElement
instance IsSVGExternalResourcesRequired SVGScriptElement
instance IsGObject SVGScriptElement where
typeGType _ = gTypeSVGScriptElement
{-# INLINE typeGType #-}
noSVGScriptElement :: Maybe SVGScriptElement
noSVGScriptElement = Nothing
{-# INLINE noSVGScriptElement #-}
gTypeSVGScriptElement :: JSM GType
gTypeSVGScriptElement = GType . Object <$> jsg "SVGScriptElement"
newtype SVGSetElement = SVGSetElement { unSVGSetElement :: JSVal }
instance PToJSVal SVGSetElement where
pToJSVal = unSVGSetElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGSetElement where
pFromJSVal = SVGSetElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGSetElement where
toJSVal = return . unSVGSetElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGSetElement where
fromJSVal v = fmap SVGSetElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGSetElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGSetElement where
makeObject = makeObject . unSVGSetElement
instance IsSVGAnimationElement SVGSetElement
instance IsSVGElement SVGSetElement
instance IsElement SVGSetElement
instance IsNode SVGSetElement
instance IsEventTarget SVGSetElement
instance IsSlotable SVGSetElement
instance IsParentNode SVGSetElement
instance IsNonDocumentTypeChildNode SVGSetElement
instance IsDocumentAndElementEventHandlers SVGSetElement
instance IsChildNode SVGSetElement
instance IsAnimatable SVGSetElement
instance IsGlobalEventHandlers SVGSetElement
instance IsElementCSSInlineStyle SVGSetElement
instance IsSVGTests SVGSetElement
instance IsSVGExternalResourcesRequired SVGSetElement
instance IsGObject SVGSetElement where
typeGType _ = gTypeSVGSetElement
{-# INLINE typeGType #-}
noSVGSetElement :: Maybe SVGSetElement
noSVGSetElement = Nothing
{-# INLINE noSVGSetElement #-}
gTypeSVGSetElement :: JSM GType
gTypeSVGSetElement = GType . Object <$> jsg "SVGSetElement"
newtype SVGStopElement = SVGStopElement { unSVGStopElement :: JSVal }
instance PToJSVal SVGStopElement where
pToJSVal = unSVGStopElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGStopElement where
pFromJSVal = SVGStopElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGStopElement where
toJSVal = return . unSVGStopElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGStopElement where
fromJSVal v = fmap SVGStopElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGStopElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGStopElement where
makeObject = makeObject . unSVGStopElement
instance IsSVGElement SVGStopElement
instance IsElement SVGStopElement
instance IsNode SVGStopElement
instance IsEventTarget SVGStopElement
instance IsSlotable SVGStopElement
instance IsParentNode SVGStopElement
instance IsNonDocumentTypeChildNode SVGStopElement
instance IsDocumentAndElementEventHandlers SVGStopElement
instance IsChildNode SVGStopElement
instance IsAnimatable SVGStopElement
instance IsGlobalEventHandlers SVGStopElement
instance IsElementCSSInlineStyle SVGStopElement
instance IsGObject SVGStopElement where
typeGType _ = gTypeSVGStopElement
{-# INLINE typeGType #-}
noSVGStopElement :: Maybe SVGStopElement
noSVGStopElement = Nothing
{-# INLINE noSVGStopElement #-}
gTypeSVGStopElement :: JSM GType
gTypeSVGStopElement = GType . Object <$> jsg "SVGStopElement"
newtype SVGStringList = SVGStringList { unSVGStringList :: JSVal }
instance PToJSVal SVGStringList where
pToJSVal = unSVGStringList
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGStringList where
pFromJSVal = SVGStringList
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGStringList where
toJSVal = return . unSVGStringList
{-# INLINE toJSVal #-}
instance FromJSVal SVGStringList where
fromJSVal v = fmap SVGStringList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGStringList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGStringList where
makeObject = makeObject . unSVGStringList
instance IsGObject SVGStringList where
typeGType _ = gTypeSVGStringList
{-# INLINE typeGType #-}
noSVGStringList :: Maybe SVGStringList
noSVGStringList = Nothing
{-# INLINE noSVGStringList #-}
gTypeSVGStringList :: JSM GType
gTypeSVGStringList = GType . Object <$> jsg "SVGStringList"
newtype SVGStyleElement = SVGStyleElement { unSVGStyleElement :: JSVal }
instance PToJSVal SVGStyleElement where
pToJSVal = unSVGStyleElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGStyleElement where
pFromJSVal = SVGStyleElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGStyleElement where
toJSVal = return . unSVGStyleElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGStyleElement where
fromJSVal v = fmap SVGStyleElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGStyleElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGStyleElement where
makeObject = makeObject . unSVGStyleElement
instance IsSVGElement SVGStyleElement
instance IsElement SVGStyleElement
instance IsNode SVGStyleElement
instance IsEventTarget SVGStyleElement
instance IsSlotable SVGStyleElement
instance IsParentNode SVGStyleElement
instance IsNonDocumentTypeChildNode SVGStyleElement
instance IsDocumentAndElementEventHandlers SVGStyleElement
instance IsChildNode SVGStyleElement
instance IsAnimatable SVGStyleElement
instance IsGlobalEventHandlers SVGStyleElement
instance IsElementCSSInlineStyle SVGStyleElement
instance IsGObject SVGStyleElement where
typeGType _ = gTypeSVGStyleElement
{-# INLINE typeGType #-}
noSVGStyleElement :: Maybe SVGStyleElement
noSVGStyleElement = Nothing
{-# INLINE noSVGStyleElement #-}
gTypeSVGStyleElement :: JSM GType
gTypeSVGStyleElement = GType . Object <$> jsg "SVGStyleElement"
newtype SVGSwitchElement = SVGSwitchElement { unSVGSwitchElement :: JSVal }
instance PToJSVal SVGSwitchElement where
pToJSVal = unSVGSwitchElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGSwitchElement where
pFromJSVal = SVGSwitchElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGSwitchElement where
toJSVal = return . unSVGSwitchElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGSwitchElement where
fromJSVal v = fmap SVGSwitchElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGSwitchElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGSwitchElement where
makeObject = makeObject . unSVGSwitchElement
instance IsSVGGraphicsElement SVGSwitchElement
instance IsSVGElement SVGSwitchElement
instance IsElement SVGSwitchElement
instance IsNode SVGSwitchElement
instance IsEventTarget SVGSwitchElement
instance IsSlotable SVGSwitchElement
instance IsParentNode SVGSwitchElement
instance IsNonDocumentTypeChildNode SVGSwitchElement
instance IsDocumentAndElementEventHandlers SVGSwitchElement
instance IsChildNode SVGSwitchElement
instance IsAnimatable SVGSwitchElement
instance IsGlobalEventHandlers SVGSwitchElement
instance IsElementCSSInlineStyle SVGSwitchElement
instance IsSVGTests SVGSwitchElement
instance IsSVGExternalResourcesRequired SVGSwitchElement
instance IsGObject SVGSwitchElement where
typeGType _ = gTypeSVGSwitchElement
{-# INLINE typeGType #-}
noSVGSwitchElement :: Maybe SVGSwitchElement
noSVGSwitchElement = Nothing
{-# INLINE noSVGSwitchElement #-}
gTypeSVGSwitchElement :: JSM GType
gTypeSVGSwitchElement = GType . Object <$> jsg "SVGSwitchElement"
newtype SVGSymbolElement = SVGSymbolElement { unSVGSymbolElement :: JSVal }
instance PToJSVal SVGSymbolElement where
pToJSVal = unSVGSymbolElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGSymbolElement where
pFromJSVal = SVGSymbolElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGSymbolElement where
toJSVal = return . unSVGSymbolElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGSymbolElement where
fromJSVal v = fmap SVGSymbolElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGSymbolElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGSymbolElement where
makeObject = makeObject . unSVGSymbolElement
instance IsSVGElement SVGSymbolElement
instance IsElement SVGSymbolElement
instance IsNode SVGSymbolElement
instance IsEventTarget SVGSymbolElement
instance IsSlotable SVGSymbolElement
instance IsParentNode SVGSymbolElement
instance IsNonDocumentTypeChildNode SVGSymbolElement
instance IsDocumentAndElementEventHandlers SVGSymbolElement
instance IsChildNode SVGSymbolElement
instance IsAnimatable SVGSymbolElement
instance IsGlobalEventHandlers SVGSymbolElement
instance IsElementCSSInlineStyle SVGSymbolElement
instance IsSVGFitToViewBox SVGSymbolElement
instance IsSVGExternalResourcesRequired SVGSymbolElement
instance IsGObject SVGSymbolElement where
typeGType _ = gTypeSVGSymbolElement
{-# INLINE typeGType #-}
noSVGSymbolElement :: Maybe SVGSymbolElement
noSVGSymbolElement = Nothing
{-# INLINE noSVGSymbolElement #-}
gTypeSVGSymbolElement :: JSM GType
gTypeSVGSymbolElement = GType . Object <$> jsg "SVGSymbolElement"
newtype SVGTRefElement = SVGTRefElement { unSVGTRefElement :: JSVal }
instance PToJSVal SVGTRefElement where
pToJSVal = unSVGTRefElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGTRefElement where
pFromJSVal = SVGTRefElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGTRefElement where
toJSVal = return . unSVGTRefElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGTRefElement where
fromJSVal v = fmap SVGTRefElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGTRefElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGTRefElement where
makeObject = makeObject . unSVGTRefElement
instance IsSVGTextPositioningElement SVGTRefElement
instance IsSVGTextContentElement SVGTRefElement
instance IsSVGGraphicsElement SVGTRefElement
instance IsSVGElement SVGTRefElement
instance IsElement SVGTRefElement
instance IsNode SVGTRefElement
instance IsEventTarget SVGTRefElement
instance IsSlotable SVGTRefElement
instance IsParentNode SVGTRefElement
instance IsNonDocumentTypeChildNode SVGTRefElement
instance IsDocumentAndElementEventHandlers SVGTRefElement
instance IsChildNode SVGTRefElement
instance IsAnimatable SVGTRefElement
instance IsGlobalEventHandlers SVGTRefElement
instance IsElementCSSInlineStyle SVGTRefElement
instance IsSVGTests SVGTRefElement
instance IsSVGExternalResourcesRequired SVGTRefElement
instance IsSVGURIReference SVGTRefElement
instance IsGObject SVGTRefElement where
typeGType _ = gTypeSVGTRefElement
{-# INLINE typeGType #-}
noSVGTRefElement :: Maybe SVGTRefElement
noSVGTRefElement = Nothing
{-# INLINE noSVGTRefElement #-}
gTypeSVGTRefElement :: JSM GType
gTypeSVGTRefElement = GType . Object <$> jsg "SVGTRefElement"
newtype SVGTSpanElement = SVGTSpanElement { unSVGTSpanElement :: JSVal }
instance PToJSVal SVGTSpanElement where
pToJSVal = unSVGTSpanElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGTSpanElement where
pFromJSVal = SVGTSpanElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGTSpanElement where
toJSVal = return . unSVGTSpanElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGTSpanElement where
fromJSVal v = fmap SVGTSpanElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGTSpanElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGTSpanElement where
makeObject = makeObject . unSVGTSpanElement
instance IsSVGTextPositioningElement SVGTSpanElement
instance IsSVGTextContentElement SVGTSpanElement
instance IsSVGGraphicsElement SVGTSpanElement
instance IsSVGElement SVGTSpanElement
instance IsElement SVGTSpanElement
instance IsNode SVGTSpanElement
instance IsEventTarget SVGTSpanElement
instance IsSlotable SVGTSpanElement
instance IsParentNode SVGTSpanElement
instance IsNonDocumentTypeChildNode SVGTSpanElement
instance IsDocumentAndElementEventHandlers SVGTSpanElement
instance IsChildNode SVGTSpanElement
instance IsAnimatable SVGTSpanElement
instance IsGlobalEventHandlers SVGTSpanElement
instance IsElementCSSInlineStyle SVGTSpanElement
instance IsSVGTests SVGTSpanElement
instance IsSVGExternalResourcesRequired SVGTSpanElement
instance IsGObject SVGTSpanElement where
typeGType _ = gTypeSVGTSpanElement
{-# INLINE typeGType #-}
noSVGTSpanElement :: Maybe SVGTSpanElement
noSVGTSpanElement = Nothing
{-# INLINE noSVGTSpanElement #-}
gTypeSVGTSpanElement :: JSM GType
gTypeSVGTSpanElement = GType . Object <$> jsg "SVGTSpanElement"
newtype SVGTests = SVGTests { unSVGTests :: JSVal }
instance PToJSVal SVGTests where
pToJSVal = unSVGTests
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGTests where
pFromJSVal = SVGTests
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGTests where
toJSVal = return . unSVGTests
{-# INLINE toJSVal #-}
instance FromJSVal SVGTests where
fromJSVal v = fmap SVGTests <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGTests
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGTests where
makeObject = makeObject . unSVGTests
class (IsGObject o) => IsSVGTests o
toSVGTests :: IsSVGTests o => o -> SVGTests
toSVGTests = SVGTests . coerce
instance IsSVGTests SVGTests
instance IsGObject SVGTests where
typeGType _ = gTypeSVGTests
{-# INLINE typeGType #-}
noSVGTests :: Maybe SVGTests
noSVGTests = Nothing
{-# INLINE noSVGTests #-}
gTypeSVGTests :: JSM GType
gTypeSVGTests = GType . Object <$> jsg "SVGTests"
newtype SVGTextContentElement = SVGTextContentElement { unSVGTextContentElement :: JSVal }
instance PToJSVal SVGTextContentElement where
pToJSVal = unSVGTextContentElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGTextContentElement where
pFromJSVal = SVGTextContentElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGTextContentElement where
toJSVal = return . unSVGTextContentElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGTextContentElement where
fromJSVal v = fmap SVGTextContentElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGTextContentElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGTextContentElement where
makeObject = makeObject . unSVGTextContentElement
class (IsSVGGraphicsElement o, IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsSVGTests o, IsSVGExternalResourcesRequired o, IsGObject o) => IsSVGTextContentElement o
toSVGTextContentElement :: IsSVGTextContentElement o => o -> SVGTextContentElement
toSVGTextContentElement = SVGTextContentElement . coerce
instance IsSVGTextContentElement SVGTextContentElement
instance IsSVGGraphicsElement SVGTextContentElement
instance IsSVGElement SVGTextContentElement
instance IsElement SVGTextContentElement
instance IsNode SVGTextContentElement
instance IsEventTarget SVGTextContentElement
instance IsSlotable SVGTextContentElement
instance IsParentNode SVGTextContentElement
instance IsNonDocumentTypeChildNode SVGTextContentElement
instance IsDocumentAndElementEventHandlers SVGTextContentElement
instance IsChildNode SVGTextContentElement
instance IsAnimatable SVGTextContentElement
instance IsGlobalEventHandlers SVGTextContentElement
instance IsElementCSSInlineStyle SVGTextContentElement
instance IsSVGTests SVGTextContentElement
instance IsSVGExternalResourcesRequired SVGTextContentElement
instance IsGObject SVGTextContentElement where
typeGType _ = gTypeSVGTextContentElement
{-# INLINE typeGType #-}
noSVGTextContentElement :: Maybe SVGTextContentElement
noSVGTextContentElement = Nothing
{-# INLINE noSVGTextContentElement #-}
gTypeSVGTextContentElement :: JSM GType
gTypeSVGTextContentElement = GType . Object <$> jsg "SVGTextContentElement"
newtype SVGTextElement = SVGTextElement { unSVGTextElement :: JSVal }
instance PToJSVal SVGTextElement where
pToJSVal = unSVGTextElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGTextElement where
pFromJSVal = SVGTextElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGTextElement where
toJSVal = return . unSVGTextElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGTextElement where
fromJSVal v = fmap SVGTextElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGTextElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGTextElement where
makeObject = makeObject . unSVGTextElement
instance IsSVGTextPositioningElement SVGTextElement
instance IsSVGTextContentElement SVGTextElement
instance IsSVGGraphicsElement SVGTextElement
instance IsSVGElement SVGTextElement
instance IsElement SVGTextElement
instance IsNode SVGTextElement
instance IsEventTarget SVGTextElement
instance IsSlotable SVGTextElement
instance IsParentNode SVGTextElement
instance IsNonDocumentTypeChildNode SVGTextElement
instance IsDocumentAndElementEventHandlers SVGTextElement
instance IsChildNode SVGTextElement
instance IsAnimatable SVGTextElement
instance IsGlobalEventHandlers SVGTextElement
instance IsElementCSSInlineStyle SVGTextElement
instance IsSVGTests SVGTextElement
instance IsSVGExternalResourcesRequired SVGTextElement
instance IsGObject SVGTextElement where
typeGType _ = gTypeSVGTextElement
{-# INLINE typeGType #-}
noSVGTextElement :: Maybe SVGTextElement
noSVGTextElement = Nothing
{-# INLINE noSVGTextElement #-}
gTypeSVGTextElement :: JSM GType
gTypeSVGTextElement = GType . Object <$> jsg "SVGTextElement"
newtype SVGTextPathElement = SVGTextPathElement { unSVGTextPathElement :: JSVal }
instance PToJSVal SVGTextPathElement where
pToJSVal = unSVGTextPathElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGTextPathElement where
pFromJSVal = SVGTextPathElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGTextPathElement where
toJSVal = return . unSVGTextPathElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGTextPathElement where
fromJSVal v = fmap SVGTextPathElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGTextPathElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGTextPathElement where
makeObject = makeObject . unSVGTextPathElement
instance IsSVGTextContentElement SVGTextPathElement
instance IsSVGGraphicsElement SVGTextPathElement
instance IsSVGElement SVGTextPathElement
instance IsElement SVGTextPathElement
instance IsNode SVGTextPathElement
instance IsEventTarget SVGTextPathElement
instance IsSlotable SVGTextPathElement
instance IsParentNode SVGTextPathElement
instance IsNonDocumentTypeChildNode SVGTextPathElement
instance IsDocumentAndElementEventHandlers SVGTextPathElement
instance IsChildNode SVGTextPathElement
instance IsAnimatable SVGTextPathElement
instance IsGlobalEventHandlers SVGTextPathElement
instance IsElementCSSInlineStyle SVGTextPathElement
instance IsSVGTests SVGTextPathElement
instance IsSVGExternalResourcesRequired SVGTextPathElement
instance IsSVGURIReference SVGTextPathElement
instance IsGObject SVGTextPathElement where
typeGType _ = gTypeSVGTextPathElement
{-# INLINE typeGType #-}
noSVGTextPathElement :: Maybe SVGTextPathElement
noSVGTextPathElement = Nothing
{-# INLINE noSVGTextPathElement #-}
gTypeSVGTextPathElement :: JSM GType
gTypeSVGTextPathElement = GType . Object <$> jsg "SVGTextPathElement"
newtype SVGTextPositioningElement = SVGTextPositioningElement { unSVGTextPositioningElement :: JSVal }
instance PToJSVal SVGTextPositioningElement where
pToJSVal = unSVGTextPositioningElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGTextPositioningElement where
pFromJSVal = SVGTextPositioningElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGTextPositioningElement where
toJSVal = return . unSVGTextPositioningElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGTextPositioningElement where
fromJSVal v = fmap SVGTextPositioningElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGTextPositioningElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGTextPositioningElement where
makeObject = makeObject . unSVGTextPositioningElement
class (IsSVGTextContentElement o, IsSVGGraphicsElement o, IsSVGElement o, IsElement o, IsNode o, IsEventTarget o, IsSlotable o, IsParentNode o, IsNonDocumentTypeChildNode o, IsDocumentAndElementEventHandlers o, IsChildNode o, IsAnimatable o, IsGlobalEventHandlers o, IsElementCSSInlineStyle o, IsSVGTests o, IsSVGExternalResourcesRequired o, IsGObject o) => IsSVGTextPositioningElement o
toSVGTextPositioningElement :: IsSVGTextPositioningElement o => o -> SVGTextPositioningElement
toSVGTextPositioningElement = SVGTextPositioningElement . coerce
instance IsSVGTextPositioningElement SVGTextPositioningElement
instance IsSVGTextContentElement SVGTextPositioningElement
instance IsSVGGraphicsElement SVGTextPositioningElement
instance IsSVGElement SVGTextPositioningElement
instance IsElement SVGTextPositioningElement
instance IsNode SVGTextPositioningElement
instance IsEventTarget SVGTextPositioningElement
instance IsSlotable SVGTextPositioningElement
instance IsParentNode SVGTextPositioningElement
instance IsNonDocumentTypeChildNode SVGTextPositioningElement
instance IsDocumentAndElementEventHandlers SVGTextPositioningElement
instance IsChildNode SVGTextPositioningElement
instance IsAnimatable SVGTextPositioningElement
instance IsGlobalEventHandlers SVGTextPositioningElement
instance IsElementCSSInlineStyle SVGTextPositioningElement
instance IsSVGTests SVGTextPositioningElement
instance IsSVGExternalResourcesRequired SVGTextPositioningElement
instance IsGObject SVGTextPositioningElement where
typeGType _ = gTypeSVGTextPositioningElement
{-# INLINE typeGType #-}
noSVGTextPositioningElement :: Maybe SVGTextPositioningElement
noSVGTextPositioningElement = Nothing
{-# INLINE noSVGTextPositioningElement #-}
gTypeSVGTextPositioningElement :: JSM GType
gTypeSVGTextPositioningElement = GType . Object <$> jsg "SVGTextPositioningElement"
newtype SVGTitleElement = SVGTitleElement { unSVGTitleElement :: JSVal }
instance PToJSVal SVGTitleElement where
pToJSVal = unSVGTitleElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGTitleElement where
pFromJSVal = SVGTitleElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGTitleElement where
toJSVal = return . unSVGTitleElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGTitleElement where
fromJSVal v = fmap SVGTitleElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGTitleElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGTitleElement where
makeObject = makeObject . unSVGTitleElement
instance IsSVGElement SVGTitleElement
instance IsElement SVGTitleElement
instance IsNode SVGTitleElement
instance IsEventTarget SVGTitleElement
instance IsSlotable SVGTitleElement
instance IsParentNode SVGTitleElement
instance IsNonDocumentTypeChildNode SVGTitleElement
instance IsDocumentAndElementEventHandlers SVGTitleElement
instance IsChildNode SVGTitleElement
instance IsAnimatable SVGTitleElement
instance IsGlobalEventHandlers SVGTitleElement
instance IsElementCSSInlineStyle SVGTitleElement
instance IsGObject SVGTitleElement where
typeGType _ = gTypeSVGTitleElement
{-# INLINE typeGType #-}
noSVGTitleElement :: Maybe SVGTitleElement
noSVGTitleElement = Nothing
{-# INLINE noSVGTitleElement #-}
gTypeSVGTitleElement :: JSM GType
gTypeSVGTitleElement = GType . Object <$> jsg "SVGTitleElement"
newtype SVGTransform = SVGTransform { unSVGTransform :: JSVal }
instance PToJSVal SVGTransform where
pToJSVal = unSVGTransform
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGTransform where
pFromJSVal = SVGTransform
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGTransform where
toJSVal = return . unSVGTransform
{-# INLINE toJSVal #-}
instance FromJSVal SVGTransform where
fromJSVal v = fmap SVGTransform <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGTransform
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGTransform where
makeObject = makeObject . unSVGTransform
instance IsGObject SVGTransform where
typeGType _ = gTypeSVGTransform
{-# INLINE typeGType #-}
noSVGTransform :: Maybe SVGTransform
noSVGTransform = Nothing
{-# INLINE noSVGTransform #-}
gTypeSVGTransform :: JSM GType
gTypeSVGTransform = GType . Object <$> jsg "SVGTransform"
newtype SVGTransformList = SVGTransformList { unSVGTransformList :: JSVal }
instance PToJSVal SVGTransformList where
pToJSVal = unSVGTransformList
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGTransformList where
pFromJSVal = SVGTransformList
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGTransformList where
toJSVal = return . unSVGTransformList
{-# INLINE toJSVal #-}
instance FromJSVal SVGTransformList where
fromJSVal v = fmap SVGTransformList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGTransformList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGTransformList where
makeObject = makeObject . unSVGTransformList
instance IsGObject SVGTransformList where
typeGType _ = gTypeSVGTransformList
{-# INLINE typeGType #-}
noSVGTransformList :: Maybe SVGTransformList
noSVGTransformList = Nothing
{-# INLINE noSVGTransformList #-}
gTypeSVGTransformList :: JSM GType
gTypeSVGTransformList = GType . Object <$> jsg "SVGTransformList"
newtype SVGURIReference = SVGURIReference { unSVGURIReference :: JSVal }
instance PToJSVal SVGURIReference where
pToJSVal = unSVGURIReference
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGURIReference where
pFromJSVal = SVGURIReference
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGURIReference where
toJSVal = return . unSVGURIReference
{-# INLINE toJSVal #-}
instance FromJSVal SVGURIReference where
fromJSVal v = fmap SVGURIReference <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGURIReference
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGURIReference where
makeObject = makeObject . unSVGURIReference
class (IsGObject o) => IsSVGURIReference o
toSVGURIReference :: IsSVGURIReference o => o -> SVGURIReference
toSVGURIReference = SVGURIReference . coerce
instance IsSVGURIReference SVGURIReference
instance IsGObject SVGURIReference where
typeGType _ = gTypeSVGURIReference
{-# INLINE typeGType #-}
noSVGURIReference :: Maybe SVGURIReference
noSVGURIReference = Nothing
{-# INLINE noSVGURIReference #-}
gTypeSVGURIReference :: JSM GType
gTypeSVGURIReference = GType . Object <$> jsg "SVGURIReference"
newtype SVGUnitTypes = SVGUnitTypes { unSVGUnitTypes :: JSVal }
instance PToJSVal SVGUnitTypes where
pToJSVal = unSVGUnitTypes
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGUnitTypes where
pFromJSVal = SVGUnitTypes
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGUnitTypes where
toJSVal = return . unSVGUnitTypes
{-# INLINE toJSVal #-}
instance FromJSVal SVGUnitTypes where
fromJSVal v = fmap SVGUnitTypes <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGUnitTypes
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGUnitTypes where
makeObject = makeObject . unSVGUnitTypes
instance IsGObject SVGUnitTypes where
typeGType _ = gTypeSVGUnitTypes
{-# INLINE typeGType #-}
noSVGUnitTypes :: Maybe SVGUnitTypes
noSVGUnitTypes = Nothing
{-# INLINE noSVGUnitTypes #-}
gTypeSVGUnitTypes :: JSM GType
gTypeSVGUnitTypes = GType . Object <$> jsg "SVGUnitTypes"
newtype SVGUseElement = SVGUseElement { unSVGUseElement :: JSVal }
instance PToJSVal SVGUseElement where
pToJSVal = unSVGUseElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGUseElement where
pFromJSVal = SVGUseElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGUseElement where
toJSVal = return . unSVGUseElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGUseElement where
fromJSVal v = fmap SVGUseElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGUseElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGUseElement where
makeObject = makeObject . unSVGUseElement
instance IsSVGGraphicsElement SVGUseElement
instance IsSVGElement SVGUseElement
instance IsElement SVGUseElement
instance IsNode SVGUseElement
instance IsEventTarget SVGUseElement
instance IsSlotable SVGUseElement
instance IsParentNode SVGUseElement
instance IsNonDocumentTypeChildNode SVGUseElement
instance IsDocumentAndElementEventHandlers SVGUseElement
instance IsChildNode SVGUseElement
instance IsAnimatable SVGUseElement
instance IsGlobalEventHandlers SVGUseElement
instance IsElementCSSInlineStyle SVGUseElement
instance IsSVGTests SVGUseElement
instance IsSVGURIReference SVGUseElement
instance IsSVGExternalResourcesRequired SVGUseElement
instance IsGObject SVGUseElement where
typeGType _ = gTypeSVGUseElement
{-# INLINE typeGType #-}
noSVGUseElement :: Maybe SVGUseElement
noSVGUseElement = Nothing
{-# INLINE noSVGUseElement #-}
gTypeSVGUseElement :: JSM GType
gTypeSVGUseElement = GType . Object <$> jsg "SVGUseElement"
newtype SVGVKernElement = SVGVKernElement { unSVGVKernElement :: JSVal }
instance PToJSVal SVGVKernElement where
pToJSVal = unSVGVKernElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGVKernElement where
pFromJSVal = SVGVKernElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGVKernElement where
toJSVal = return . unSVGVKernElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGVKernElement where
fromJSVal v = fmap SVGVKernElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGVKernElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGVKernElement where
makeObject = makeObject . unSVGVKernElement
instance IsSVGElement SVGVKernElement
instance IsElement SVGVKernElement
instance IsNode SVGVKernElement
instance IsEventTarget SVGVKernElement
instance IsSlotable SVGVKernElement
instance IsParentNode SVGVKernElement
instance IsNonDocumentTypeChildNode SVGVKernElement
instance IsDocumentAndElementEventHandlers SVGVKernElement
instance IsChildNode SVGVKernElement
instance IsAnimatable SVGVKernElement
instance IsGlobalEventHandlers SVGVKernElement
instance IsElementCSSInlineStyle SVGVKernElement
instance IsGObject SVGVKernElement where
typeGType _ = gTypeSVGVKernElement
{-# INLINE typeGType #-}
noSVGVKernElement :: Maybe SVGVKernElement
noSVGVKernElement = Nothing
{-# INLINE noSVGVKernElement #-}
gTypeSVGVKernElement :: JSM GType
gTypeSVGVKernElement = GType . Object <$> jsg "SVGVKernElement"
newtype SVGViewElement = SVGViewElement { unSVGViewElement :: JSVal }
instance PToJSVal SVGViewElement where
pToJSVal = unSVGViewElement
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGViewElement where
pFromJSVal = SVGViewElement
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGViewElement where
toJSVal = return . unSVGViewElement
{-# INLINE toJSVal #-}
instance FromJSVal SVGViewElement where
fromJSVal v = fmap SVGViewElement <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGViewElement
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGViewElement where
makeObject = makeObject . unSVGViewElement
instance IsSVGElement SVGViewElement
instance IsElement SVGViewElement
instance IsNode SVGViewElement
instance IsEventTarget SVGViewElement
instance IsSlotable SVGViewElement
instance IsParentNode SVGViewElement
instance IsNonDocumentTypeChildNode SVGViewElement
instance IsDocumentAndElementEventHandlers SVGViewElement
instance IsChildNode SVGViewElement
instance IsAnimatable SVGViewElement
instance IsGlobalEventHandlers SVGViewElement
instance IsElementCSSInlineStyle SVGViewElement
instance IsSVGZoomAndPan SVGViewElement
instance IsSVGFitToViewBox SVGViewElement
instance IsSVGExternalResourcesRequired SVGViewElement
instance IsGObject SVGViewElement where
typeGType _ = gTypeSVGViewElement
{-# INLINE typeGType #-}
noSVGViewElement :: Maybe SVGViewElement
noSVGViewElement = Nothing
{-# INLINE noSVGViewElement #-}
gTypeSVGViewElement :: JSM GType
gTypeSVGViewElement = GType . Object <$> jsg "SVGViewElement"
newtype SVGViewSpec = SVGViewSpec { unSVGViewSpec :: JSVal }
instance PToJSVal SVGViewSpec where
pToJSVal = unSVGViewSpec
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGViewSpec where
pFromJSVal = SVGViewSpec
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGViewSpec where
toJSVal = return . unSVGViewSpec
{-# INLINE toJSVal #-}
instance FromJSVal SVGViewSpec where
fromJSVal v = fmap SVGViewSpec <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGViewSpec
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGViewSpec where
makeObject = makeObject . unSVGViewSpec
instance IsSVGFitToViewBox SVGViewSpec
instance IsGObject SVGViewSpec where
typeGType _ = gTypeSVGViewSpec
{-# INLINE typeGType #-}
noSVGViewSpec :: Maybe SVGViewSpec
noSVGViewSpec = Nothing
{-# INLINE noSVGViewSpec #-}
gTypeSVGViewSpec :: JSM GType
gTypeSVGViewSpec = GType . Object <$> jsg "SVGViewSpec"
newtype SVGZoomAndPan = SVGZoomAndPan { unSVGZoomAndPan :: JSVal }
instance PToJSVal SVGZoomAndPan where
pToJSVal = unSVGZoomAndPan
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGZoomAndPan where
pFromJSVal = SVGZoomAndPan
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGZoomAndPan where
toJSVal = return . unSVGZoomAndPan
{-# INLINE toJSVal #-}
instance FromJSVal SVGZoomAndPan where
fromJSVal v = fmap SVGZoomAndPan <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGZoomAndPan
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGZoomAndPan where
makeObject = makeObject . unSVGZoomAndPan
class (IsGObject o) => IsSVGZoomAndPan o
toSVGZoomAndPan :: IsSVGZoomAndPan o => o -> SVGZoomAndPan
toSVGZoomAndPan = SVGZoomAndPan . coerce
instance IsSVGZoomAndPan SVGZoomAndPan
instance IsGObject SVGZoomAndPan where
typeGType _ = gTypeSVGZoomAndPan
{-# INLINE typeGType #-}
noSVGZoomAndPan :: Maybe SVGZoomAndPan
noSVGZoomAndPan = Nothing
{-# INLINE noSVGZoomAndPan #-}
gTypeSVGZoomAndPan :: JSM GType
gTypeSVGZoomAndPan = GType . Object <$> jsg "SVGZoomAndPan"
newtype SVGZoomEvent = SVGZoomEvent { unSVGZoomEvent :: JSVal }
instance PToJSVal SVGZoomEvent where
pToJSVal = unSVGZoomEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal SVGZoomEvent where
pFromJSVal = SVGZoomEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal SVGZoomEvent where
toJSVal = return . unSVGZoomEvent
{-# INLINE toJSVal #-}
instance FromJSVal SVGZoomEvent where
fromJSVal v = fmap SVGZoomEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SVGZoomEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SVGZoomEvent where
makeObject = makeObject . unSVGZoomEvent
instance IsUIEvent SVGZoomEvent
instance IsEvent SVGZoomEvent
instance IsGObject SVGZoomEvent where
typeGType _ = gTypeSVGZoomEvent
{-# INLINE typeGType #-}
noSVGZoomEvent :: Maybe SVGZoomEvent
noSVGZoomEvent = Nothing
{-# INLINE noSVGZoomEvent #-}
gTypeSVGZoomEvent :: JSM GType
gTypeSVGZoomEvent = GType . Object <$> jsg "SVGZoomEvent"
newtype Screen = Screen { unScreen :: JSVal }
instance PToJSVal Screen where
pToJSVal = unScreen
{-# INLINE pToJSVal #-}
instance PFromJSVal Screen where
pFromJSVal = Screen
{-# INLINE pFromJSVal #-}
instance ToJSVal Screen where
toJSVal = return . unScreen
{-# INLINE toJSVal #-}
instance FromJSVal Screen where
fromJSVal v = fmap Screen <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Screen
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Screen where
makeObject = makeObject . unScreen
instance IsGObject Screen where
typeGType _ = gTypeScreen
{-# INLINE typeGType #-}
noScreen :: Maybe Screen
noScreen = Nothing
{-# INLINE noScreen #-}
gTypeScreen :: JSM GType
gTypeScreen = GType . Object <$> jsg "Screen"
newtype ScriptProcessorNode = ScriptProcessorNode { unScriptProcessorNode :: JSVal }
instance PToJSVal ScriptProcessorNode where
pToJSVal = unScriptProcessorNode
{-# INLINE pToJSVal #-}
instance PFromJSVal ScriptProcessorNode where
pFromJSVal = ScriptProcessorNode
{-# INLINE pFromJSVal #-}
instance ToJSVal ScriptProcessorNode where
toJSVal = return . unScriptProcessorNode
{-# INLINE toJSVal #-}
instance FromJSVal ScriptProcessorNode where
fromJSVal v = fmap ScriptProcessorNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ScriptProcessorNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ScriptProcessorNode where
makeObject = makeObject . unScriptProcessorNode
instance IsAudioNode ScriptProcessorNode
instance IsEventTarget ScriptProcessorNode
instance IsGObject ScriptProcessorNode where
typeGType _ = gTypeScriptProcessorNode
{-# INLINE typeGType #-}
noScriptProcessorNode :: Maybe ScriptProcessorNode
noScriptProcessorNode = Nothing
{-# INLINE noScriptProcessorNode #-}
gTypeScriptProcessorNode :: JSM GType
gTypeScriptProcessorNode = GType . Object <$> jsg "ScriptProcessorNode"
newtype ScrollToOptions = ScrollToOptions { unScrollToOptions :: JSVal }
instance PToJSVal ScrollToOptions where
pToJSVal = unScrollToOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal ScrollToOptions where
pFromJSVal = ScrollToOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal ScrollToOptions where
toJSVal = return . unScrollToOptions
{-# INLINE toJSVal #-}
instance FromJSVal ScrollToOptions where
fromJSVal v = fmap ScrollToOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ScrollToOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ScrollToOptions where
makeObject = makeObject . unScrollToOptions
instance IsGObject ScrollToOptions where
typeGType _ = gTypeScrollToOptions
{-# INLINE typeGType #-}
noScrollToOptions :: Maybe ScrollToOptions
noScrollToOptions = Nothing
{-# INLINE noScrollToOptions #-}
gTypeScrollToOptions :: JSM GType
gTypeScrollToOptions = GType . Object <$> jsg "ScrollToOptions"
newtype SecurityPolicyViolationEvent = SecurityPolicyViolationEvent { unSecurityPolicyViolationEvent :: JSVal }
instance PToJSVal SecurityPolicyViolationEvent where
pToJSVal = unSecurityPolicyViolationEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal SecurityPolicyViolationEvent where
pFromJSVal = SecurityPolicyViolationEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal SecurityPolicyViolationEvent where
toJSVal = return . unSecurityPolicyViolationEvent
{-# INLINE toJSVal #-}
instance FromJSVal SecurityPolicyViolationEvent where
fromJSVal v = fmap SecurityPolicyViolationEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SecurityPolicyViolationEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SecurityPolicyViolationEvent where
makeObject = makeObject . unSecurityPolicyViolationEvent
instance IsEvent SecurityPolicyViolationEvent
instance IsGObject SecurityPolicyViolationEvent where
typeGType _ = gTypeSecurityPolicyViolationEvent
{-# INLINE typeGType #-}
noSecurityPolicyViolationEvent :: Maybe SecurityPolicyViolationEvent
noSecurityPolicyViolationEvent = Nothing
{-# INLINE noSecurityPolicyViolationEvent #-}
gTypeSecurityPolicyViolationEvent :: JSM GType
gTypeSecurityPolicyViolationEvent = GType . Object <$> jsg "SecurityPolicyViolationEvent"
newtype SecurityPolicyViolationEventInit = SecurityPolicyViolationEventInit { unSecurityPolicyViolationEventInit :: JSVal }
instance PToJSVal SecurityPolicyViolationEventInit where
pToJSVal = unSecurityPolicyViolationEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal SecurityPolicyViolationEventInit where
pFromJSVal = SecurityPolicyViolationEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal SecurityPolicyViolationEventInit where
toJSVal = return . unSecurityPolicyViolationEventInit
{-# INLINE toJSVal #-}
instance FromJSVal SecurityPolicyViolationEventInit where
fromJSVal v = fmap SecurityPolicyViolationEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SecurityPolicyViolationEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SecurityPolicyViolationEventInit where
makeObject = makeObject . unSecurityPolicyViolationEventInit
instance IsEventInit SecurityPolicyViolationEventInit
instance IsGObject SecurityPolicyViolationEventInit where
typeGType _ = gTypeSecurityPolicyViolationEventInit
{-# INLINE typeGType #-}
noSecurityPolicyViolationEventInit :: Maybe SecurityPolicyViolationEventInit
noSecurityPolicyViolationEventInit = Nothing
{-# INLINE noSecurityPolicyViolationEventInit #-}
gTypeSecurityPolicyViolationEventInit :: JSM GType
gTypeSecurityPolicyViolationEventInit = GType . Object <$> jsg "SecurityPolicyViolationEventInit"
newtype Selection = Selection { unSelection :: JSVal }
instance PToJSVal Selection where
pToJSVal = unSelection
{-# INLINE pToJSVal #-}
instance PFromJSVal Selection where
pFromJSVal = Selection
{-# INLINE pFromJSVal #-}
instance ToJSVal Selection where
toJSVal = return . unSelection
{-# INLINE toJSVal #-}
instance FromJSVal Selection where
fromJSVal v = fmap Selection <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Selection
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Selection where
makeObject = makeObject . unSelection
instance IsGObject Selection where
typeGType _ = gTypeSelection
{-# INLINE typeGType #-}
noSelection :: Maybe Selection
noSelection = Nothing
{-# INLINE noSelection #-}
gTypeSelection :: JSM GType
gTypeSelection = GType . Object <$> jsg "Selection"
newtype ShadowRoot = ShadowRoot { unShadowRoot :: JSVal }
instance PToJSVal ShadowRoot where
pToJSVal = unShadowRoot
{-# INLINE pToJSVal #-}
instance PFromJSVal ShadowRoot where
pFromJSVal = ShadowRoot
{-# INLINE pFromJSVal #-}
instance ToJSVal ShadowRoot where
toJSVal = return . unShadowRoot
{-# INLINE toJSVal #-}
instance FromJSVal ShadowRoot where
fromJSVal v = fmap ShadowRoot <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ShadowRoot
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ShadowRoot where
makeObject = makeObject . unShadowRoot
instance IsDocumentFragment ShadowRoot
instance IsNode ShadowRoot
instance IsEventTarget ShadowRoot
instance IsNonElementParentNode ShadowRoot
instance IsParentNode ShadowRoot
instance IsDocumentOrShadowRoot ShadowRoot
instance IsGObject ShadowRoot where
typeGType _ = gTypeShadowRoot
{-# INLINE typeGType #-}
noShadowRoot :: Maybe ShadowRoot
noShadowRoot = Nothing
{-# INLINE noShadowRoot #-}
gTypeShadowRoot :: JSM GType
gTypeShadowRoot = GType . Object <$> jsg "ShadowRoot"
newtype ShadowRootInit = ShadowRootInit { unShadowRootInit :: JSVal }
instance PToJSVal ShadowRootInit where
pToJSVal = unShadowRootInit
{-# INLINE pToJSVal #-}
instance PFromJSVal ShadowRootInit where
pFromJSVal = ShadowRootInit
{-# INLINE pFromJSVal #-}
instance ToJSVal ShadowRootInit where
toJSVal = return . unShadowRootInit
{-# INLINE toJSVal #-}
instance FromJSVal ShadowRootInit where
fromJSVal v = fmap ShadowRootInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ShadowRootInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ShadowRootInit where
makeObject = makeObject . unShadowRootInit
instance IsGObject ShadowRootInit where
typeGType _ = gTypeShadowRootInit
{-# INLINE typeGType #-}
noShadowRootInit :: Maybe ShadowRootInit
noShadowRootInit = Nothing
{-# INLINE noShadowRootInit #-}
gTypeShadowRootInit :: JSM GType
gTypeShadowRootInit = GType . Object <$> jsg "ShadowRootInit"
newtype SiteBoundCredential = SiteBoundCredential { unSiteBoundCredential :: JSVal }
instance PToJSVal SiteBoundCredential where
pToJSVal = unSiteBoundCredential
{-# INLINE pToJSVal #-}
instance PFromJSVal SiteBoundCredential where
pFromJSVal = SiteBoundCredential
{-# INLINE pFromJSVal #-}
instance ToJSVal SiteBoundCredential where
toJSVal = return . unSiteBoundCredential
{-# INLINE toJSVal #-}
instance FromJSVal SiteBoundCredential where
fromJSVal v = fmap SiteBoundCredential <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SiteBoundCredential
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SiteBoundCredential where
makeObject = makeObject . unSiteBoundCredential
class (IsBasicCredential o, IsGObject o) => IsSiteBoundCredential o
toSiteBoundCredential :: IsSiteBoundCredential o => o -> SiteBoundCredential
toSiteBoundCredential = SiteBoundCredential . coerce
instance IsSiteBoundCredential SiteBoundCredential
instance IsBasicCredential SiteBoundCredential
instance IsGObject SiteBoundCredential where
typeGType _ = gTypeSiteBoundCredential
{-# INLINE typeGType #-}
noSiteBoundCredential :: Maybe SiteBoundCredential
noSiteBoundCredential = Nothing
{-# INLINE noSiteBoundCredential #-}
gTypeSiteBoundCredential :: JSM GType
gTypeSiteBoundCredential = GType . Object <$> jsg "SiteBoundCredential"
newtype SiteBoundCredentialData = SiteBoundCredentialData { unSiteBoundCredentialData :: JSVal }
instance PToJSVal SiteBoundCredentialData where
pToJSVal = unSiteBoundCredentialData
{-# INLINE pToJSVal #-}
instance PFromJSVal SiteBoundCredentialData where
pFromJSVal = SiteBoundCredentialData
{-# INLINE pFromJSVal #-}
instance ToJSVal SiteBoundCredentialData where
toJSVal = return . unSiteBoundCredentialData
{-# INLINE toJSVal #-}
instance FromJSVal SiteBoundCredentialData where
fromJSVal v = fmap SiteBoundCredentialData <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SiteBoundCredentialData
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SiteBoundCredentialData where
makeObject = makeObject . unSiteBoundCredentialData
class (IsCredentialData o, IsGObject o) => IsSiteBoundCredentialData o
toSiteBoundCredentialData :: IsSiteBoundCredentialData o => o -> SiteBoundCredentialData
toSiteBoundCredentialData = SiteBoundCredentialData . coerce
instance IsSiteBoundCredentialData SiteBoundCredentialData
instance IsCredentialData SiteBoundCredentialData
instance IsGObject SiteBoundCredentialData where
typeGType _ = gTypeSiteBoundCredentialData
{-# INLINE typeGType #-}
noSiteBoundCredentialData :: Maybe SiteBoundCredentialData
noSiteBoundCredentialData = Nothing
{-# INLINE noSiteBoundCredentialData #-}
gTypeSiteBoundCredentialData :: JSM GType
gTypeSiteBoundCredentialData = GType . Object <$> jsg "SiteBoundCredentialData"
newtype Slotable = Slotable { unSlotable :: JSVal }
instance PToJSVal Slotable where
pToJSVal = unSlotable
{-# INLINE pToJSVal #-}
instance PFromJSVal Slotable where
pFromJSVal = Slotable
{-# INLINE pFromJSVal #-}
instance ToJSVal Slotable where
toJSVal = return . unSlotable
{-# INLINE toJSVal #-}
instance FromJSVal Slotable where
fromJSVal v = fmap Slotable <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Slotable
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Slotable where
makeObject = makeObject . unSlotable
class (IsGObject o) => IsSlotable o
toSlotable :: IsSlotable o => o -> Slotable
toSlotable = Slotable . coerce
instance IsSlotable Slotable
instance IsGObject Slotable where
typeGType _ = gTypeSlotable
{-# INLINE typeGType #-}
noSlotable :: Maybe Slotable
noSlotable = Nothing
{-# INLINE noSlotable #-}
gTypeSlotable :: JSM GType
gTypeSlotable = GType . Object <$> jsg "Slotable"
newtype SourceBuffer = SourceBuffer { unSourceBuffer :: JSVal }
instance PToJSVal SourceBuffer where
pToJSVal = unSourceBuffer
{-# INLINE pToJSVal #-}
instance PFromJSVal SourceBuffer where
pFromJSVal = SourceBuffer
{-# INLINE pFromJSVal #-}
instance ToJSVal SourceBuffer where
toJSVal = return . unSourceBuffer
{-# INLINE toJSVal #-}
instance FromJSVal SourceBuffer where
fromJSVal v = fmap SourceBuffer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SourceBuffer
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SourceBuffer where
makeObject = makeObject . unSourceBuffer
instance IsEventTarget SourceBuffer
instance IsGObject SourceBuffer where
typeGType _ = gTypeSourceBuffer
{-# INLINE typeGType #-}
noSourceBuffer :: Maybe SourceBuffer
noSourceBuffer = Nothing
{-# INLINE noSourceBuffer #-}
gTypeSourceBuffer :: JSM GType
gTypeSourceBuffer = GType . Object <$> jsg "SourceBuffer"
newtype SourceBufferList = SourceBufferList { unSourceBufferList :: JSVal }
instance PToJSVal SourceBufferList where
pToJSVal = unSourceBufferList
{-# INLINE pToJSVal #-}
instance PFromJSVal SourceBufferList where
pFromJSVal = SourceBufferList
{-# INLINE pFromJSVal #-}
instance ToJSVal SourceBufferList where
toJSVal = return . unSourceBufferList
{-# INLINE toJSVal #-}
instance FromJSVal SourceBufferList where
fromJSVal v = fmap SourceBufferList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SourceBufferList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SourceBufferList where
makeObject = makeObject . unSourceBufferList
instance IsEventTarget SourceBufferList
instance IsGObject SourceBufferList where
typeGType _ = gTypeSourceBufferList
{-# INLINE typeGType #-}
noSourceBufferList :: Maybe SourceBufferList
noSourceBufferList = Nothing
{-# INLINE noSourceBufferList #-}
gTypeSourceBufferList :: JSM GType
gTypeSourceBufferList = GType . Object <$> jsg "SourceBufferList"
newtype SpeechSynthesis = SpeechSynthesis { unSpeechSynthesis :: JSVal }
instance PToJSVal SpeechSynthesis where
pToJSVal = unSpeechSynthesis
{-# INLINE pToJSVal #-}
instance PFromJSVal SpeechSynthesis where
pFromJSVal = SpeechSynthesis
{-# INLINE pFromJSVal #-}
instance ToJSVal SpeechSynthesis where
toJSVal = return . unSpeechSynthesis
{-# INLINE toJSVal #-}
instance FromJSVal SpeechSynthesis where
fromJSVal v = fmap SpeechSynthesis <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SpeechSynthesis
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SpeechSynthesis where
makeObject = makeObject . unSpeechSynthesis
instance IsGObject SpeechSynthesis where
typeGType _ = gTypeSpeechSynthesis
{-# INLINE typeGType #-}
noSpeechSynthesis :: Maybe SpeechSynthesis
noSpeechSynthesis = Nothing
{-# INLINE noSpeechSynthesis #-}
gTypeSpeechSynthesis :: JSM GType
gTypeSpeechSynthesis = GType . Object <$> jsg "SpeechSynthesis"
newtype SpeechSynthesisEvent = SpeechSynthesisEvent { unSpeechSynthesisEvent :: JSVal }
instance PToJSVal SpeechSynthesisEvent where
pToJSVal = unSpeechSynthesisEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal SpeechSynthesisEvent where
pFromJSVal = SpeechSynthesisEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal SpeechSynthesisEvent where
toJSVal = return . unSpeechSynthesisEvent
{-# INLINE toJSVal #-}
instance FromJSVal SpeechSynthesisEvent where
fromJSVal v = fmap SpeechSynthesisEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SpeechSynthesisEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SpeechSynthesisEvent where
makeObject = makeObject . unSpeechSynthesisEvent
instance IsEvent SpeechSynthesisEvent
instance IsGObject SpeechSynthesisEvent where
typeGType _ = gTypeSpeechSynthesisEvent
{-# INLINE typeGType #-}
noSpeechSynthesisEvent :: Maybe SpeechSynthesisEvent
noSpeechSynthesisEvent = Nothing
{-# INLINE noSpeechSynthesisEvent #-}
gTypeSpeechSynthesisEvent :: JSM GType
gTypeSpeechSynthesisEvent = GType . Object <$> jsg "SpeechSynthesisEvent"
newtype SpeechSynthesisUtterance = SpeechSynthesisUtterance { unSpeechSynthesisUtterance :: JSVal }
instance PToJSVal SpeechSynthesisUtterance where
pToJSVal = unSpeechSynthesisUtterance
{-# INLINE pToJSVal #-}
instance PFromJSVal SpeechSynthesisUtterance where
pFromJSVal = SpeechSynthesisUtterance
{-# INLINE pFromJSVal #-}
instance ToJSVal SpeechSynthesisUtterance where
toJSVal = return . unSpeechSynthesisUtterance
{-# INLINE toJSVal #-}
instance FromJSVal SpeechSynthesisUtterance where
fromJSVal v = fmap SpeechSynthesisUtterance <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SpeechSynthesisUtterance
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SpeechSynthesisUtterance where
makeObject = makeObject . unSpeechSynthesisUtterance
instance IsEventTarget SpeechSynthesisUtterance
instance IsGObject SpeechSynthesisUtterance where
typeGType _ = gTypeSpeechSynthesisUtterance
{-# INLINE typeGType #-}
noSpeechSynthesisUtterance :: Maybe SpeechSynthesisUtterance
noSpeechSynthesisUtterance = Nothing
{-# INLINE noSpeechSynthesisUtterance #-}
gTypeSpeechSynthesisUtterance :: JSM GType
gTypeSpeechSynthesisUtterance = GType . Object <$> jsg "SpeechSynthesisUtterance"
newtype SpeechSynthesisVoice = SpeechSynthesisVoice { unSpeechSynthesisVoice :: JSVal }
instance PToJSVal SpeechSynthesisVoice where
pToJSVal = unSpeechSynthesisVoice
{-# INLINE pToJSVal #-}
instance PFromJSVal SpeechSynthesisVoice where
pFromJSVal = SpeechSynthesisVoice
{-# INLINE pFromJSVal #-}
instance ToJSVal SpeechSynthesisVoice where
toJSVal = return . unSpeechSynthesisVoice
{-# INLINE toJSVal #-}
instance FromJSVal SpeechSynthesisVoice where
fromJSVal v = fmap SpeechSynthesisVoice <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SpeechSynthesisVoice
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SpeechSynthesisVoice where
makeObject = makeObject . unSpeechSynthesisVoice
instance IsGObject SpeechSynthesisVoice where
typeGType _ = gTypeSpeechSynthesisVoice
{-# INLINE typeGType #-}
noSpeechSynthesisVoice :: Maybe SpeechSynthesisVoice
noSpeechSynthesisVoice = Nothing
{-# INLINE noSpeechSynthesisVoice #-}
gTypeSpeechSynthesisVoice :: JSM GType
gTypeSpeechSynthesisVoice = GType . Object <$> jsg "SpeechSynthesisVoice"
newtype StaticRange = StaticRange { unStaticRange :: JSVal }
instance PToJSVal StaticRange where
pToJSVal = unStaticRange
{-# INLINE pToJSVal #-}
instance PFromJSVal StaticRange where
pFromJSVal = StaticRange
{-# INLINE pFromJSVal #-}
instance ToJSVal StaticRange where
toJSVal = return . unStaticRange
{-# INLINE toJSVal #-}
instance FromJSVal StaticRange where
fromJSVal v = fmap StaticRange <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . StaticRange
{-# INLINE fromJSValUnchecked #-}
instance MakeObject StaticRange where
makeObject = makeObject . unStaticRange
instance IsGObject StaticRange where
typeGType _ = gTypeStaticRange
{-# INLINE typeGType #-}
noStaticRange :: Maybe StaticRange
noStaticRange = Nothing
{-# INLINE noStaticRange #-}
gTypeStaticRange :: JSM GType
gTypeStaticRange = GType . Object <$> jsg "StaticRange"
newtype Storage = Storage { unStorage :: JSVal }
instance PToJSVal Storage where
pToJSVal = unStorage
{-# INLINE pToJSVal #-}
instance PFromJSVal Storage where
pFromJSVal = Storage
{-# INLINE pFromJSVal #-}
instance ToJSVal Storage where
toJSVal = return . unStorage
{-# INLINE toJSVal #-}
instance FromJSVal Storage where
fromJSVal v = fmap Storage <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Storage
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Storage where
makeObject = makeObject . unStorage
instance IsGObject Storage where
typeGType _ = gTypeStorage
{-# INLINE typeGType #-}
noStorage :: Maybe Storage
noStorage = Nothing
{-# INLINE noStorage #-}
gTypeStorage :: JSM GType
gTypeStorage = GType . Object <$> jsg "Storage"
newtype StorageEvent = StorageEvent { unStorageEvent :: JSVal }
instance PToJSVal StorageEvent where
pToJSVal = unStorageEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal StorageEvent where
pFromJSVal = StorageEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal StorageEvent where
toJSVal = return . unStorageEvent
{-# INLINE toJSVal #-}
instance FromJSVal StorageEvent where
fromJSVal v = fmap StorageEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . StorageEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject StorageEvent where
makeObject = makeObject . unStorageEvent
instance IsEvent StorageEvent
instance IsGObject StorageEvent where
typeGType _ = gTypeStorageEvent
{-# INLINE typeGType #-}
noStorageEvent :: Maybe StorageEvent
noStorageEvent = Nothing
{-# INLINE noStorageEvent #-}
gTypeStorageEvent :: JSM GType
gTypeStorageEvent = GType . Object <$> jsg "StorageEvent"
newtype StorageEventInit = StorageEventInit { unStorageEventInit :: JSVal }
instance PToJSVal StorageEventInit where
pToJSVal = unStorageEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal StorageEventInit where
pFromJSVal = StorageEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal StorageEventInit where
toJSVal = return . unStorageEventInit
{-# INLINE toJSVal #-}
instance FromJSVal StorageEventInit where
fromJSVal v = fmap StorageEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . StorageEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject StorageEventInit where
makeObject = makeObject . unStorageEventInit
instance IsEventInit StorageEventInit
instance IsGObject StorageEventInit where
typeGType _ = gTypeStorageEventInit
{-# INLINE typeGType #-}
noStorageEventInit :: Maybe StorageEventInit
noStorageEventInit = Nothing
{-# INLINE noStorageEventInit #-}
gTypeStorageEventInit :: JSM GType
gTypeStorageEventInit = GType . Object <$> jsg "StorageEventInit"
newtype StorageInfo = StorageInfo { unStorageInfo :: JSVal }
instance PToJSVal StorageInfo where
pToJSVal = unStorageInfo
{-# INLINE pToJSVal #-}
instance PFromJSVal StorageInfo where
pFromJSVal = StorageInfo
{-# INLINE pFromJSVal #-}
instance ToJSVal StorageInfo where
toJSVal = return . unStorageInfo
{-# INLINE toJSVal #-}
instance FromJSVal StorageInfo where
fromJSVal v = fmap StorageInfo <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . StorageInfo
{-# INLINE fromJSValUnchecked #-}
instance MakeObject StorageInfo where
makeObject = makeObject . unStorageInfo
instance IsGObject StorageInfo where
typeGType _ = gTypeStorageInfo
{-# INLINE typeGType #-}
noStorageInfo :: Maybe StorageInfo
noStorageInfo = Nothing
{-# INLINE noStorageInfo #-}
gTypeStorageInfo :: JSM GType
gTypeStorageInfo = GType . Object <$> jsg "StorageInfo"
newtype StorageQuota = StorageQuota { unStorageQuota :: JSVal }
instance PToJSVal StorageQuota where
pToJSVal = unStorageQuota
{-# INLINE pToJSVal #-}
instance PFromJSVal StorageQuota where
pFromJSVal = StorageQuota
{-# INLINE pFromJSVal #-}
instance ToJSVal StorageQuota where
toJSVal = return . unStorageQuota
{-# INLINE toJSVal #-}
instance FromJSVal StorageQuota where
fromJSVal v = fmap StorageQuota <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . StorageQuota
{-# INLINE fromJSValUnchecked #-}
instance MakeObject StorageQuota where
makeObject = makeObject . unStorageQuota
instance IsGObject StorageQuota where
typeGType _ = gTypeStorageQuota
{-# INLINE typeGType #-}
noStorageQuota :: Maybe StorageQuota
noStorageQuota = Nothing
{-# INLINE noStorageQuota #-}
gTypeStorageQuota :: JSM GType
gTypeStorageQuota = GType . Object <$> jsg "StorageQuota"
newtype StyleMedia = StyleMedia { unStyleMedia :: JSVal }
instance PToJSVal StyleMedia where
pToJSVal = unStyleMedia
{-# INLINE pToJSVal #-}
instance PFromJSVal StyleMedia where
pFromJSVal = StyleMedia
{-# INLINE pFromJSVal #-}
instance ToJSVal StyleMedia where
toJSVal = return . unStyleMedia
{-# INLINE toJSVal #-}
instance FromJSVal StyleMedia where
fromJSVal v = fmap StyleMedia <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . StyleMedia
{-# INLINE fromJSValUnchecked #-}
instance MakeObject StyleMedia where
makeObject = makeObject . unStyleMedia
instance IsGObject StyleMedia where
typeGType _ = gTypeStyleMedia
{-# INLINE typeGType #-}
noStyleMedia :: Maybe StyleMedia
noStyleMedia = Nothing
{-# INLINE noStyleMedia #-}
gTypeStyleMedia :: JSM GType
gTypeStyleMedia = GType . Object <$> jsg "StyleMedia"
newtype StyleSheet = StyleSheet { unStyleSheet :: JSVal }
instance PToJSVal StyleSheet where
pToJSVal = unStyleSheet
{-# INLINE pToJSVal #-}
instance PFromJSVal StyleSheet where
pFromJSVal = StyleSheet
{-# INLINE pFromJSVal #-}
instance ToJSVal StyleSheet where
toJSVal = return . unStyleSheet
{-# INLINE toJSVal #-}
instance FromJSVal StyleSheet where
fromJSVal v = fmap StyleSheet <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . StyleSheet
{-# INLINE fromJSValUnchecked #-}
instance MakeObject StyleSheet where
makeObject = makeObject . unStyleSheet
class (IsGObject o) => IsStyleSheet o
toStyleSheet :: IsStyleSheet o => o -> StyleSheet
toStyleSheet = StyleSheet . coerce
instance IsStyleSheet StyleSheet
instance IsGObject StyleSheet where
typeGType _ = gTypeStyleSheet
{-# INLINE typeGType #-}
noStyleSheet :: Maybe StyleSheet
noStyleSheet = Nothing
{-# INLINE noStyleSheet #-}
gTypeStyleSheet :: JSM GType
gTypeStyleSheet = GType . Object <$> jsg "StyleSheet"
newtype StyleSheetList = StyleSheetList { unStyleSheetList :: JSVal }
instance PToJSVal StyleSheetList where
pToJSVal = unStyleSheetList
{-# INLINE pToJSVal #-}
instance PFromJSVal StyleSheetList where
pFromJSVal = StyleSheetList
{-# INLINE pFromJSVal #-}
instance ToJSVal StyleSheetList where
toJSVal = return . unStyleSheetList
{-# INLINE toJSVal #-}
instance FromJSVal StyleSheetList where
fromJSVal v = fmap StyleSheetList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . StyleSheetList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject StyleSheetList where
makeObject = makeObject . unStyleSheetList
instance IsGObject StyleSheetList where
typeGType _ = gTypeStyleSheetList
{-# INLINE typeGType #-}
noStyleSheetList :: Maybe StyleSheetList
noStyleSheetList = Nothing
{-# INLINE noStyleSheetList #-}
gTypeStyleSheetList :: JSM GType
gTypeStyleSheetList = GType . Object <$> jsg "StyleSheetList"
newtype SubtleCrypto = SubtleCrypto { unSubtleCrypto :: JSVal }
instance PToJSVal SubtleCrypto where
pToJSVal = unSubtleCrypto
{-# INLINE pToJSVal #-}
instance PFromJSVal SubtleCrypto where
pFromJSVal = SubtleCrypto
{-# INLINE pFromJSVal #-}
instance ToJSVal SubtleCrypto where
toJSVal = return . unSubtleCrypto
{-# INLINE toJSVal #-}
instance FromJSVal SubtleCrypto where
fromJSVal v = fmap SubtleCrypto <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . SubtleCrypto
{-# INLINE fromJSValUnchecked #-}
instance MakeObject SubtleCrypto where
makeObject = makeObject . unSubtleCrypto
instance IsGObject SubtleCrypto where
typeGType _ = gTypeSubtleCrypto
{-# INLINE typeGType #-}
noSubtleCrypto :: Maybe SubtleCrypto
noSubtleCrypto = Nothing
{-# INLINE noSubtleCrypto #-}
gTypeSubtleCrypto :: JSM GType
gTypeSubtleCrypto = GType . Object <$> jsg "WebKitSubtleCrypto"
newtype Text = Text { unText :: JSVal }
instance PToJSVal Text where
pToJSVal = unText
{-# INLINE pToJSVal #-}
instance PFromJSVal Text where
pFromJSVal = Text
{-# INLINE pFromJSVal #-}
instance ToJSVal Text where
toJSVal = return . unText
{-# INLINE toJSVal #-}
instance FromJSVal Text where
fromJSVal v = fmap Text <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Text
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Text where
makeObject = makeObject . unText
class (IsCharacterData o, IsNode o, IsEventTarget o, IsNonDocumentTypeChildNode o, IsChildNode o, IsSlotable o, IsGObject o) => IsText o
toText :: IsText o => o -> Text
toText = Text . coerce
instance IsText Text
instance IsCharacterData Text
instance IsNode Text
instance IsEventTarget Text
instance IsNonDocumentTypeChildNode Text
instance IsChildNode Text
instance IsSlotable Text
instance IsGObject Text where
typeGType _ = gTypeText
{-# INLINE typeGType #-}
noText :: Maybe Text
noText = Nothing
{-# INLINE noText #-}
gTypeText :: JSM GType
gTypeText = GType . Object <$> jsg "Text"
newtype TextDecodeOptions = TextDecodeOptions { unTextDecodeOptions :: JSVal }
instance PToJSVal TextDecodeOptions where
pToJSVal = unTextDecodeOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal TextDecodeOptions where
pFromJSVal = TextDecodeOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal TextDecodeOptions where
toJSVal = return . unTextDecodeOptions
{-# INLINE toJSVal #-}
instance FromJSVal TextDecodeOptions where
fromJSVal v = fmap TextDecodeOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TextDecodeOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TextDecodeOptions where
makeObject = makeObject . unTextDecodeOptions
instance IsGObject TextDecodeOptions where
typeGType _ = gTypeTextDecodeOptions
{-# INLINE typeGType #-}
noTextDecodeOptions :: Maybe TextDecodeOptions
noTextDecodeOptions = Nothing
{-# INLINE noTextDecodeOptions #-}
gTypeTextDecodeOptions :: JSM GType
gTypeTextDecodeOptions = GType . Object <$> jsg "TextDecodeOptions"
newtype TextDecoder = TextDecoder { unTextDecoder :: JSVal }
instance PToJSVal TextDecoder where
pToJSVal = unTextDecoder
{-# INLINE pToJSVal #-}
instance PFromJSVal TextDecoder where
pFromJSVal = TextDecoder
{-# INLINE pFromJSVal #-}
instance ToJSVal TextDecoder where
toJSVal = return . unTextDecoder
{-# INLINE toJSVal #-}
instance FromJSVal TextDecoder where
fromJSVal v = fmap TextDecoder <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TextDecoder
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TextDecoder where
makeObject = makeObject . unTextDecoder
instance IsGObject TextDecoder where
typeGType _ = gTypeTextDecoder
{-# INLINE typeGType #-}
noTextDecoder :: Maybe TextDecoder
noTextDecoder = Nothing
{-# INLINE noTextDecoder #-}
gTypeTextDecoder :: JSM GType
gTypeTextDecoder = GType . Object <$> jsg "TextDecoder"
newtype TextDecoderOptions = TextDecoderOptions { unTextDecoderOptions :: JSVal }
instance PToJSVal TextDecoderOptions where
pToJSVal = unTextDecoderOptions
{-# INLINE pToJSVal #-}
instance PFromJSVal TextDecoderOptions where
pFromJSVal = TextDecoderOptions
{-# INLINE pFromJSVal #-}
instance ToJSVal TextDecoderOptions where
toJSVal = return . unTextDecoderOptions
{-# INLINE toJSVal #-}
instance FromJSVal TextDecoderOptions where
fromJSVal v = fmap TextDecoderOptions <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TextDecoderOptions
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TextDecoderOptions where
makeObject = makeObject . unTextDecoderOptions
instance IsGObject TextDecoderOptions where
typeGType _ = gTypeTextDecoderOptions
{-# INLINE typeGType #-}
noTextDecoderOptions :: Maybe TextDecoderOptions
noTextDecoderOptions = Nothing
{-# INLINE noTextDecoderOptions #-}
gTypeTextDecoderOptions :: JSM GType
gTypeTextDecoderOptions = GType . Object <$> jsg "TextDecoderOptions"
newtype TextEncoder = TextEncoder { unTextEncoder :: JSVal }
instance PToJSVal TextEncoder where
pToJSVal = unTextEncoder
{-# INLINE pToJSVal #-}
instance PFromJSVal TextEncoder where
pFromJSVal = TextEncoder
{-# INLINE pFromJSVal #-}
instance ToJSVal TextEncoder where
toJSVal = return . unTextEncoder
{-# INLINE toJSVal #-}
instance FromJSVal TextEncoder where
fromJSVal v = fmap TextEncoder <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TextEncoder
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TextEncoder where
makeObject = makeObject . unTextEncoder
instance IsGObject TextEncoder where
typeGType _ = gTypeTextEncoder
{-# INLINE typeGType #-}
noTextEncoder :: Maybe TextEncoder
noTextEncoder = Nothing
{-# INLINE noTextEncoder #-}
gTypeTextEncoder :: JSM GType
gTypeTextEncoder = GType . Object <$> jsg "TextEncoder"
newtype TextEvent = TextEvent { unTextEvent :: JSVal }
instance PToJSVal TextEvent where
pToJSVal = unTextEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal TextEvent where
pFromJSVal = TextEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal TextEvent where
toJSVal = return . unTextEvent
{-# INLINE toJSVal #-}
instance FromJSVal TextEvent where
fromJSVal v = fmap TextEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TextEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TextEvent where
makeObject = makeObject . unTextEvent
instance IsUIEvent TextEvent
instance IsEvent TextEvent
instance IsGObject TextEvent where
typeGType _ = gTypeTextEvent
{-# INLINE typeGType #-}
noTextEvent :: Maybe TextEvent
noTextEvent = Nothing
{-# INLINE noTextEvent #-}
gTypeTextEvent :: JSM GType
gTypeTextEvent = GType . Object <$> jsg "TextEvent"
newtype TextMetrics = TextMetrics { unTextMetrics :: JSVal }
instance PToJSVal TextMetrics where
pToJSVal = unTextMetrics
{-# INLINE pToJSVal #-}
instance PFromJSVal TextMetrics where
pFromJSVal = TextMetrics
{-# INLINE pFromJSVal #-}
instance ToJSVal TextMetrics where
toJSVal = return . unTextMetrics
{-# INLINE toJSVal #-}
instance FromJSVal TextMetrics where
fromJSVal v = fmap TextMetrics <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TextMetrics
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TextMetrics where
makeObject = makeObject . unTextMetrics
instance IsGObject TextMetrics where
typeGType _ = gTypeTextMetrics
{-# INLINE typeGType #-}
noTextMetrics :: Maybe TextMetrics
noTextMetrics = Nothing
{-# INLINE noTextMetrics #-}
gTypeTextMetrics :: JSM GType
gTypeTextMetrics = GType . Object <$> jsg "TextMetrics"
newtype TextTrack = TextTrack { unTextTrack :: JSVal }
instance PToJSVal TextTrack where
pToJSVal = unTextTrack
{-# INLINE pToJSVal #-}
instance PFromJSVal TextTrack where
pFromJSVal = TextTrack
{-# INLINE pFromJSVal #-}
instance ToJSVal TextTrack where
toJSVal = return . unTextTrack
{-# INLINE toJSVal #-}
instance FromJSVal TextTrack where
fromJSVal v = fmap TextTrack <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TextTrack
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TextTrack where
makeObject = makeObject . unTextTrack
instance IsEventTarget TextTrack
instance IsGObject TextTrack where
typeGType _ = gTypeTextTrack
{-# INLINE typeGType #-}
noTextTrack :: Maybe TextTrack
noTextTrack = Nothing
{-# INLINE noTextTrack #-}
gTypeTextTrack :: JSM GType
gTypeTextTrack = GType . Object <$> jsg "TextTrack"
newtype TextTrackCue = TextTrackCue { unTextTrackCue :: JSVal }
instance PToJSVal TextTrackCue where
pToJSVal = unTextTrackCue
{-# INLINE pToJSVal #-}
instance PFromJSVal TextTrackCue where
pFromJSVal = TextTrackCue
{-# INLINE pFromJSVal #-}
instance ToJSVal TextTrackCue where
toJSVal = return . unTextTrackCue
{-# INLINE toJSVal #-}
instance FromJSVal TextTrackCue where
fromJSVal v = fmap TextTrackCue <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TextTrackCue
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TextTrackCue where
makeObject = makeObject . unTextTrackCue
class (IsEventTarget o, IsGObject o) => IsTextTrackCue o
toTextTrackCue :: IsTextTrackCue o => o -> TextTrackCue
toTextTrackCue = TextTrackCue . coerce
instance IsTextTrackCue TextTrackCue
instance IsEventTarget TextTrackCue
instance IsGObject TextTrackCue where
typeGType _ = gTypeTextTrackCue
{-# INLINE typeGType #-}
noTextTrackCue :: Maybe TextTrackCue
noTextTrackCue = Nothing
{-# INLINE noTextTrackCue #-}
gTypeTextTrackCue :: JSM GType
gTypeTextTrackCue = GType . Object <$> jsg "TextTrackCue"
newtype TextTrackCueList = TextTrackCueList { unTextTrackCueList :: JSVal }
instance PToJSVal TextTrackCueList where
pToJSVal = unTextTrackCueList
{-# INLINE pToJSVal #-}
instance PFromJSVal TextTrackCueList where
pFromJSVal = TextTrackCueList
{-# INLINE pFromJSVal #-}
instance ToJSVal TextTrackCueList where
toJSVal = return . unTextTrackCueList
{-# INLINE toJSVal #-}
instance FromJSVal TextTrackCueList where
fromJSVal v = fmap TextTrackCueList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TextTrackCueList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TextTrackCueList where
makeObject = makeObject . unTextTrackCueList
instance IsGObject TextTrackCueList where
typeGType _ = gTypeTextTrackCueList
{-# INLINE typeGType #-}
noTextTrackCueList :: Maybe TextTrackCueList
noTextTrackCueList = Nothing
{-# INLINE noTextTrackCueList #-}
gTypeTextTrackCueList :: JSM GType
gTypeTextTrackCueList = GType . Object <$> jsg "TextTrackCueList"
newtype TextTrackList = TextTrackList { unTextTrackList :: JSVal }
instance PToJSVal TextTrackList where
pToJSVal = unTextTrackList
{-# INLINE pToJSVal #-}
instance PFromJSVal TextTrackList where
pFromJSVal = TextTrackList
{-# INLINE pFromJSVal #-}
instance ToJSVal TextTrackList where
toJSVal = return . unTextTrackList
{-# INLINE toJSVal #-}
instance FromJSVal TextTrackList where
fromJSVal v = fmap TextTrackList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TextTrackList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TextTrackList where
makeObject = makeObject . unTextTrackList
instance IsEventTarget TextTrackList
instance IsGObject TextTrackList where
typeGType _ = gTypeTextTrackList
{-# INLINE typeGType #-}
noTextTrackList :: Maybe TextTrackList
noTextTrackList = Nothing
{-# INLINE noTextTrackList #-}
gTypeTextTrackList :: JSM GType
gTypeTextTrackList = GType . Object <$> jsg "TextTrackList"
newtype TimeRanges = TimeRanges { unTimeRanges :: JSVal }
instance PToJSVal TimeRanges where
pToJSVal = unTimeRanges
{-# INLINE pToJSVal #-}
instance PFromJSVal TimeRanges where
pFromJSVal = TimeRanges
{-# INLINE pFromJSVal #-}
instance ToJSVal TimeRanges where
toJSVal = return . unTimeRanges
{-# INLINE toJSVal #-}
instance FromJSVal TimeRanges where
fromJSVal v = fmap TimeRanges <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TimeRanges
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TimeRanges where
makeObject = makeObject . unTimeRanges
instance IsGObject TimeRanges where
typeGType _ = gTypeTimeRanges
{-# INLINE typeGType #-}
noTimeRanges :: Maybe TimeRanges
noTimeRanges = Nothing
{-# INLINE noTimeRanges #-}
gTypeTimeRanges :: JSM GType
gTypeTimeRanges = GType . Object <$> jsg "TimeRanges"
newtype Touch = Touch { unTouch :: JSVal }
instance PToJSVal Touch where
pToJSVal = unTouch
{-# INLINE pToJSVal #-}
instance PFromJSVal Touch where
pFromJSVal = Touch
{-# INLINE pFromJSVal #-}
instance ToJSVal Touch where
toJSVal = return . unTouch
{-# INLINE toJSVal #-}
instance FromJSVal Touch where
fromJSVal v = fmap Touch <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Touch
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Touch where
makeObject = makeObject . unTouch
instance IsGObject Touch where
typeGType _ = gTypeTouch
{-# INLINE typeGType #-}
noTouch :: Maybe Touch
noTouch = Nothing
{-# INLINE noTouch #-}
gTypeTouch :: JSM GType
gTypeTouch = GType . Object <$> jsg "Touch"
newtype TouchEvent = TouchEvent { unTouchEvent :: JSVal }
instance PToJSVal TouchEvent where
pToJSVal = unTouchEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal TouchEvent where
pFromJSVal = TouchEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal TouchEvent where
toJSVal = return . unTouchEvent
{-# INLINE toJSVal #-}
instance FromJSVal TouchEvent where
fromJSVal v = fmap TouchEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TouchEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TouchEvent where
makeObject = makeObject . unTouchEvent
instance IsUIEvent TouchEvent
instance IsEvent TouchEvent
instance IsGObject TouchEvent where
typeGType _ = gTypeTouchEvent
{-# INLINE typeGType #-}
noTouchEvent :: Maybe TouchEvent
noTouchEvent = Nothing
{-# INLINE noTouchEvent #-}
gTypeTouchEvent :: JSM GType
gTypeTouchEvent = GType . Object <$> jsg "TouchEvent"
newtype TouchEventInit = TouchEventInit { unTouchEventInit :: JSVal }
instance PToJSVal TouchEventInit where
pToJSVal = unTouchEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal TouchEventInit where
pFromJSVal = TouchEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal TouchEventInit where
toJSVal = return . unTouchEventInit
{-# INLINE toJSVal #-}
instance FromJSVal TouchEventInit where
fromJSVal v = fmap TouchEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TouchEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TouchEventInit where
makeObject = makeObject . unTouchEventInit
instance IsUIEventInit TouchEventInit
instance IsEventInit TouchEventInit
instance IsGObject TouchEventInit where
typeGType _ = gTypeTouchEventInit
{-# INLINE typeGType #-}
noTouchEventInit :: Maybe TouchEventInit
noTouchEventInit = Nothing
{-# INLINE noTouchEventInit #-}
gTypeTouchEventInit :: JSM GType
gTypeTouchEventInit = GType . Object <$> jsg "TouchEventInit"
newtype TouchList = TouchList { unTouchList :: JSVal }
instance PToJSVal TouchList where
pToJSVal = unTouchList
{-# INLINE pToJSVal #-}
instance PFromJSVal TouchList where
pFromJSVal = TouchList
{-# INLINE pFromJSVal #-}
instance ToJSVal TouchList where
toJSVal = return . unTouchList
{-# INLINE toJSVal #-}
instance FromJSVal TouchList where
fromJSVal v = fmap TouchList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TouchList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TouchList where
makeObject = makeObject . unTouchList
instance IsGObject TouchList where
typeGType _ = gTypeTouchList
{-# INLINE typeGType #-}
noTouchList :: Maybe TouchList
noTouchList = Nothing
{-# INLINE noTouchList #-}
gTypeTouchList :: JSM GType
gTypeTouchList = GType . Object <$> jsg "TouchList"
newtype TrackEvent = TrackEvent { unTrackEvent :: JSVal }
instance PToJSVal TrackEvent where
pToJSVal = unTrackEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal TrackEvent where
pFromJSVal = TrackEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal TrackEvent where
toJSVal = return . unTrackEvent
{-# INLINE toJSVal #-}
instance FromJSVal TrackEvent where
fromJSVal v = fmap TrackEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TrackEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TrackEvent where
makeObject = makeObject . unTrackEvent
instance IsEvent TrackEvent
instance IsGObject TrackEvent where
typeGType _ = gTypeTrackEvent
{-# INLINE typeGType #-}
noTrackEvent :: Maybe TrackEvent
noTrackEvent = Nothing
{-# INLINE noTrackEvent #-}
gTypeTrackEvent :: JSM GType
gTypeTrackEvent = GType . Object <$> jsg "TrackEvent"
newtype TrackEventInit = TrackEventInit { unTrackEventInit :: JSVal }
instance PToJSVal TrackEventInit where
pToJSVal = unTrackEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal TrackEventInit where
pFromJSVal = TrackEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal TrackEventInit where
toJSVal = return . unTrackEventInit
{-# INLINE toJSVal #-}
instance FromJSVal TrackEventInit where
fromJSVal v = fmap TrackEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TrackEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TrackEventInit where
makeObject = makeObject . unTrackEventInit
instance IsEventInit TrackEventInit
instance IsGObject TrackEventInit where
typeGType _ = gTypeTrackEventInit
{-# INLINE typeGType #-}
noTrackEventInit :: Maybe TrackEventInit
noTrackEventInit = Nothing
{-# INLINE noTrackEventInit #-}
gTypeTrackEventInit :: JSM GType
gTypeTrackEventInit = GType . Object <$> jsg "TrackEventInit"
newtype TransitionEvent = TransitionEvent { unTransitionEvent :: JSVal }
instance PToJSVal TransitionEvent where
pToJSVal = unTransitionEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal TransitionEvent where
pFromJSVal = TransitionEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal TransitionEvent where
toJSVal = return . unTransitionEvent
{-# INLINE toJSVal #-}
instance FromJSVal TransitionEvent where
fromJSVal v = fmap TransitionEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TransitionEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TransitionEvent where
makeObject = makeObject . unTransitionEvent
instance IsEvent TransitionEvent
instance IsGObject TransitionEvent where
typeGType _ = gTypeTransitionEvent
{-# INLINE typeGType #-}
noTransitionEvent :: Maybe TransitionEvent
noTransitionEvent = Nothing
{-# INLINE noTransitionEvent #-}
gTypeTransitionEvent :: JSM GType
gTypeTransitionEvent = GType . Object <$> jsg "TransitionEvent"
newtype TransitionEventInit = TransitionEventInit { unTransitionEventInit :: JSVal }
instance PToJSVal TransitionEventInit where
pToJSVal = unTransitionEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal TransitionEventInit where
pFromJSVal = TransitionEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal TransitionEventInit where
toJSVal = return . unTransitionEventInit
{-# INLINE toJSVal #-}
instance FromJSVal TransitionEventInit where
fromJSVal v = fmap TransitionEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TransitionEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TransitionEventInit where
makeObject = makeObject . unTransitionEventInit
instance IsEventInit TransitionEventInit
instance IsGObject TransitionEventInit where
typeGType _ = gTypeTransitionEventInit
{-# INLINE typeGType #-}
noTransitionEventInit :: Maybe TransitionEventInit
noTransitionEventInit = Nothing
{-# INLINE noTransitionEventInit #-}
gTypeTransitionEventInit :: JSM GType
gTypeTransitionEventInit = GType . Object <$> jsg "TransitionEventInit"
newtype TreeWalker = TreeWalker { unTreeWalker :: JSVal }
instance PToJSVal TreeWalker where
pToJSVal = unTreeWalker
{-# INLINE pToJSVal #-}
instance PFromJSVal TreeWalker where
pFromJSVal = TreeWalker
{-# INLINE pFromJSVal #-}
instance ToJSVal TreeWalker where
toJSVal = return . unTreeWalker
{-# INLINE toJSVal #-}
instance FromJSVal TreeWalker where
fromJSVal v = fmap TreeWalker <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . TreeWalker
{-# INLINE fromJSValUnchecked #-}
instance MakeObject TreeWalker where
makeObject = makeObject . unTreeWalker
instance IsGObject TreeWalker where
typeGType _ = gTypeTreeWalker
{-# INLINE typeGType #-}
noTreeWalker :: Maybe TreeWalker
noTreeWalker = Nothing
{-# INLINE noTreeWalker #-}
gTypeTreeWalker :: JSM GType
gTypeTreeWalker = GType . Object <$> jsg "TreeWalker"
newtype UIEvent = UIEvent { unUIEvent :: JSVal }
instance PToJSVal UIEvent where
pToJSVal = unUIEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal UIEvent where
pFromJSVal = UIEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal UIEvent where
toJSVal = return . unUIEvent
{-# INLINE toJSVal #-}
instance FromJSVal UIEvent where
fromJSVal v = fmap UIEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . UIEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject UIEvent where
makeObject = makeObject . unUIEvent
class (IsEvent o, IsGObject o) => IsUIEvent o
toUIEvent :: IsUIEvent o => o -> UIEvent
toUIEvent = UIEvent . coerce
instance IsUIEvent UIEvent
instance IsEvent UIEvent
instance IsGObject UIEvent where
typeGType _ = gTypeUIEvent
{-# INLINE typeGType #-}
noUIEvent :: Maybe UIEvent
noUIEvent = Nothing
{-# INLINE noUIEvent #-}
gTypeUIEvent :: JSM GType
gTypeUIEvent = GType . Object <$> jsg "UIEvent"
newtype UIEventInit = UIEventInit { unUIEventInit :: JSVal }
instance PToJSVal UIEventInit where
pToJSVal = unUIEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal UIEventInit where
pFromJSVal = UIEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal UIEventInit where
toJSVal = return . unUIEventInit
{-# INLINE toJSVal #-}
instance FromJSVal UIEventInit where
fromJSVal v = fmap UIEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . UIEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject UIEventInit where
makeObject = makeObject . unUIEventInit
class (IsEventInit o, IsGObject o) => IsUIEventInit o
toUIEventInit :: IsUIEventInit o => o -> UIEventInit
toUIEventInit = UIEventInit . coerce
instance IsUIEventInit UIEventInit
instance IsEventInit UIEventInit
instance IsGObject UIEventInit where
typeGType _ = gTypeUIEventInit
{-# INLINE typeGType #-}
noUIEventInit :: Maybe UIEventInit
noUIEventInit = Nothing
{-# INLINE noUIEventInit #-}
gTypeUIEventInit :: JSM GType
gTypeUIEventInit = GType . Object <$> jsg "UIEventInit"
newtype URL = URL { unURL :: JSVal }
instance PToJSVal URL where
pToJSVal = unURL
{-# INLINE pToJSVal #-}
instance PFromJSVal URL where
pFromJSVal = URL
{-# INLINE pFromJSVal #-}
instance ToJSVal URL where
toJSVal = return . unURL
{-# INLINE toJSVal #-}
instance FromJSVal URL where
fromJSVal v = fmap URL <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . URL
{-# INLINE fromJSValUnchecked #-}
instance MakeObject URL where
makeObject = makeObject . unURL
instance IsGObject URL where
typeGType _ = gTypeURL
{-# INLINE typeGType #-}
noURL :: Maybe URL
noURL = Nothing
{-# INLINE noURL #-}
gTypeURL :: JSM GType
gTypeURL = GType . Object <$> jsg "URL"
newtype URLSearchParams = URLSearchParams { unURLSearchParams :: JSVal }
instance PToJSVal URLSearchParams where
pToJSVal = unURLSearchParams
{-# INLINE pToJSVal #-}
instance PFromJSVal URLSearchParams where
pFromJSVal = URLSearchParams
{-# INLINE pFromJSVal #-}
instance ToJSVal URLSearchParams where
toJSVal = return . unURLSearchParams
{-# INLINE toJSVal #-}
instance FromJSVal URLSearchParams where
fromJSVal v = fmap URLSearchParams <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . URLSearchParams
{-# INLINE fromJSValUnchecked #-}
instance MakeObject URLSearchParams where
makeObject = makeObject . unURLSearchParams
instance IsGObject URLSearchParams where
typeGType _ = gTypeURLSearchParams
{-# INLINE typeGType #-}
noURLSearchParams :: Maybe URLSearchParams
noURLSearchParams = Nothing
{-# INLINE noURLSearchParams #-}
gTypeURLSearchParams :: JSM GType
gTypeURLSearchParams = GType . Object <$> jsg "URLSearchParams"
newtype UserMessageHandler = UserMessageHandler { unUserMessageHandler :: JSVal }
instance PToJSVal UserMessageHandler where
pToJSVal = unUserMessageHandler
{-# INLINE pToJSVal #-}
instance PFromJSVal UserMessageHandler where
pFromJSVal = UserMessageHandler
{-# INLINE pFromJSVal #-}
instance ToJSVal UserMessageHandler where
toJSVal = return . unUserMessageHandler
{-# INLINE toJSVal #-}
instance FromJSVal UserMessageHandler where
fromJSVal v = fmap UserMessageHandler <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . UserMessageHandler
{-# INLINE fromJSValUnchecked #-}
instance MakeObject UserMessageHandler where
makeObject = makeObject . unUserMessageHandler
instance IsGObject UserMessageHandler where
typeGType _ = gTypeUserMessageHandler
{-# INLINE typeGType #-}
noUserMessageHandler :: Maybe UserMessageHandler
noUserMessageHandler = Nothing
{-# INLINE noUserMessageHandler #-}
gTypeUserMessageHandler :: JSM GType
gTypeUserMessageHandler = GType . Object <$> jsg "UserMessageHandler"
newtype UserMessageHandlersNamespace = UserMessageHandlersNamespace { unUserMessageHandlersNamespace :: JSVal }
instance PToJSVal UserMessageHandlersNamespace where
pToJSVal = unUserMessageHandlersNamespace
{-# INLINE pToJSVal #-}
instance PFromJSVal UserMessageHandlersNamespace where
pFromJSVal = UserMessageHandlersNamespace
{-# INLINE pFromJSVal #-}
instance ToJSVal UserMessageHandlersNamespace where
toJSVal = return . unUserMessageHandlersNamespace
{-# INLINE toJSVal #-}
instance FromJSVal UserMessageHandlersNamespace where
fromJSVal v = fmap UserMessageHandlersNamespace <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . UserMessageHandlersNamespace
{-# INLINE fromJSValUnchecked #-}
instance MakeObject UserMessageHandlersNamespace where
makeObject = makeObject . unUserMessageHandlersNamespace
instance IsGObject UserMessageHandlersNamespace where
typeGType _ = gTypeUserMessageHandlersNamespace
{-# INLINE typeGType #-}
noUserMessageHandlersNamespace :: Maybe UserMessageHandlersNamespace
noUserMessageHandlersNamespace = Nothing
{-# INLINE noUserMessageHandlersNamespace #-}
gTypeUserMessageHandlersNamespace :: JSM GType
gTypeUserMessageHandlersNamespace = GType . Object <$> jsg "UserMessageHandlersNamespace"
newtype VTTCue = VTTCue { unVTTCue :: JSVal }
instance PToJSVal VTTCue where
pToJSVal = unVTTCue
{-# INLINE pToJSVal #-}
instance PFromJSVal VTTCue where
pFromJSVal = VTTCue
{-# INLINE pFromJSVal #-}
instance ToJSVal VTTCue where
toJSVal = return . unVTTCue
{-# INLINE toJSVal #-}
instance FromJSVal VTTCue where
fromJSVal v = fmap VTTCue <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . VTTCue
{-# INLINE fromJSValUnchecked #-}
instance MakeObject VTTCue where
makeObject = makeObject . unVTTCue
instance IsTextTrackCue VTTCue
instance IsEventTarget VTTCue
instance IsGObject VTTCue where
typeGType _ = gTypeVTTCue
{-# INLINE typeGType #-}
noVTTCue :: Maybe VTTCue
noVTTCue = Nothing
{-# INLINE noVTTCue #-}
gTypeVTTCue :: JSM GType
gTypeVTTCue = GType . Object <$> jsg "VTTCue"
newtype VTTRegion = VTTRegion { unVTTRegion :: JSVal }
instance PToJSVal VTTRegion where
pToJSVal = unVTTRegion
{-# INLINE pToJSVal #-}
instance PFromJSVal VTTRegion where
pFromJSVal = VTTRegion
{-# INLINE pFromJSVal #-}
instance ToJSVal VTTRegion where
toJSVal = return . unVTTRegion
{-# INLINE toJSVal #-}
instance FromJSVal VTTRegion where
fromJSVal v = fmap VTTRegion <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . VTTRegion
{-# INLINE fromJSValUnchecked #-}
instance MakeObject VTTRegion where
makeObject = makeObject . unVTTRegion
instance IsGObject VTTRegion where
typeGType _ = gTypeVTTRegion
{-# INLINE typeGType #-}
noVTTRegion :: Maybe VTTRegion
noVTTRegion = Nothing
{-# INLINE noVTTRegion #-}
gTypeVTTRegion :: JSM GType
gTypeVTTRegion = GType . Object <$> jsg "VTTRegion"
newtype VTTRegionList = VTTRegionList { unVTTRegionList :: JSVal }
instance PToJSVal VTTRegionList where
pToJSVal = unVTTRegionList
{-# INLINE pToJSVal #-}
instance PFromJSVal VTTRegionList where
pFromJSVal = VTTRegionList
{-# INLINE pFromJSVal #-}
instance ToJSVal VTTRegionList where
toJSVal = return . unVTTRegionList
{-# INLINE toJSVal #-}
instance FromJSVal VTTRegionList where
fromJSVal v = fmap VTTRegionList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . VTTRegionList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject VTTRegionList where
makeObject = makeObject . unVTTRegionList
instance IsGObject VTTRegionList where
typeGType _ = gTypeVTTRegionList
{-# INLINE typeGType #-}
noVTTRegionList :: Maybe VTTRegionList
noVTTRegionList = Nothing
{-# INLINE noVTTRegionList #-}
gTypeVTTRegionList :: JSM GType
gTypeVTTRegionList = GType . Object <$> jsg "VTTRegionList"
newtype ValidityState = ValidityState { unValidityState :: JSVal }
instance PToJSVal ValidityState where
pToJSVal = unValidityState
{-# INLINE pToJSVal #-}
instance PFromJSVal ValidityState where
pFromJSVal = ValidityState
{-# INLINE pFromJSVal #-}
instance ToJSVal ValidityState where
toJSVal = return . unValidityState
{-# INLINE toJSVal #-}
instance FromJSVal ValidityState where
fromJSVal v = fmap ValidityState <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . ValidityState
{-# INLINE fromJSValUnchecked #-}
instance MakeObject ValidityState where
makeObject = makeObject . unValidityState
instance IsGObject ValidityState where
typeGType _ = gTypeValidityState
{-# INLINE typeGType #-}
noValidityState :: Maybe ValidityState
noValidityState = Nothing
{-# INLINE noValidityState #-}
gTypeValidityState :: JSM GType
gTypeValidityState = GType . Object <$> jsg "ValidityState"
newtype VideoPlaybackQuality = VideoPlaybackQuality { unVideoPlaybackQuality :: JSVal }
instance PToJSVal VideoPlaybackQuality where
pToJSVal = unVideoPlaybackQuality
{-# INLINE pToJSVal #-}
instance PFromJSVal VideoPlaybackQuality where
pFromJSVal = VideoPlaybackQuality
{-# INLINE pFromJSVal #-}
instance ToJSVal VideoPlaybackQuality where
toJSVal = return . unVideoPlaybackQuality
{-# INLINE toJSVal #-}
instance FromJSVal VideoPlaybackQuality where
fromJSVal v = fmap VideoPlaybackQuality <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . VideoPlaybackQuality
{-# INLINE fromJSValUnchecked #-}
instance MakeObject VideoPlaybackQuality where
makeObject = makeObject . unVideoPlaybackQuality
instance IsGObject VideoPlaybackQuality where
typeGType _ = gTypeVideoPlaybackQuality
{-# INLINE typeGType #-}
noVideoPlaybackQuality :: Maybe VideoPlaybackQuality
noVideoPlaybackQuality = Nothing
{-# INLINE noVideoPlaybackQuality #-}
gTypeVideoPlaybackQuality :: JSM GType
gTypeVideoPlaybackQuality = GType . Object <$> jsg "VideoPlaybackQuality"
newtype VideoTrack = VideoTrack { unVideoTrack :: JSVal }
instance PToJSVal VideoTrack where
pToJSVal = unVideoTrack
{-# INLINE pToJSVal #-}
instance PFromJSVal VideoTrack where
pFromJSVal = VideoTrack
{-# INLINE pFromJSVal #-}
instance ToJSVal VideoTrack where
toJSVal = return . unVideoTrack
{-# INLINE toJSVal #-}
instance FromJSVal VideoTrack where
fromJSVal v = fmap VideoTrack <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . VideoTrack
{-# INLINE fromJSValUnchecked #-}
instance MakeObject VideoTrack where
makeObject = makeObject . unVideoTrack
instance IsGObject VideoTrack where
typeGType _ = gTypeVideoTrack
{-# INLINE typeGType #-}
noVideoTrack :: Maybe VideoTrack
noVideoTrack = Nothing
{-# INLINE noVideoTrack #-}
gTypeVideoTrack :: JSM GType
gTypeVideoTrack = GType . Object <$> jsg "VideoTrack"
newtype VideoTrackList = VideoTrackList { unVideoTrackList :: JSVal }
instance PToJSVal VideoTrackList where
pToJSVal = unVideoTrackList
{-# INLINE pToJSVal #-}
instance PFromJSVal VideoTrackList where
pFromJSVal = VideoTrackList
{-# INLINE pFromJSVal #-}
instance ToJSVal VideoTrackList where
toJSVal = return . unVideoTrackList
{-# INLINE toJSVal #-}
instance FromJSVal VideoTrackList where
fromJSVal v = fmap VideoTrackList <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . VideoTrackList
{-# INLINE fromJSValUnchecked #-}
instance MakeObject VideoTrackList where
makeObject = makeObject . unVideoTrackList
instance IsEventTarget VideoTrackList
instance IsGObject VideoTrackList where
typeGType _ = gTypeVideoTrackList
{-# INLINE typeGType #-}
noVideoTrackList :: Maybe VideoTrackList
noVideoTrackList = Nothing
{-# INLINE noVideoTrackList #-}
gTypeVideoTrackList :: JSM GType
gTypeVideoTrackList = GType . Object <$> jsg "VideoTrackList"
newtype WaveShaperNode = WaveShaperNode { unWaveShaperNode :: JSVal }
instance PToJSVal WaveShaperNode where
pToJSVal = unWaveShaperNode
{-# INLINE pToJSVal #-}
instance PFromJSVal WaveShaperNode where
pFromJSVal = WaveShaperNode
{-# INLINE pFromJSVal #-}
instance ToJSVal WaveShaperNode where
toJSVal = return . unWaveShaperNode
{-# INLINE toJSVal #-}
instance FromJSVal WaveShaperNode where
fromJSVal v = fmap WaveShaperNode <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WaveShaperNode
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WaveShaperNode where
makeObject = makeObject . unWaveShaperNode
instance IsAudioNode WaveShaperNode
instance IsEventTarget WaveShaperNode
instance IsGObject WaveShaperNode where
typeGType _ = gTypeWaveShaperNode
{-# INLINE typeGType #-}
noWaveShaperNode :: Maybe WaveShaperNode
noWaveShaperNode = Nothing
{-# INLINE noWaveShaperNode #-}
gTypeWaveShaperNode :: JSM GType
gTypeWaveShaperNode = GType . Object <$> jsg "WaveShaperNode"
newtype WebGL2RenderingContext = WebGL2RenderingContext { unWebGL2RenderingContext :: JSVal }
instance PToJSVal WebGL2RenderingContext where
pToJSVal = unWebGL2RenderingContext
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGL2RenderingContext where
pFromJSVal = WebGL2RenderingContext
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGL2RenderingContext where
toJSVal = return . unWebGL2RenderingContext
{-# INLINE toJSVal #-}
instance FromJSVal WebGL2RenderingContext where
fromJSVal v = fmap WebGL2RenderingContext <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGL2RenderingContext
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGL2RenderingContext where
makeObject = makeObject . unWebGL2RenderingContext
instance IsWebGLRenderingContextBase WebGL2RenderingContext
instance IsGObject WebGL2RenderingContext where
typeGType _ = gTypeWebGL2RenderingContext
{-# INLINE typeGType #-}
noWebGL2RenderingContext :: Maybe WebGL2RenderingContext
noWebGL2RenderingContext = Nothing
{-# INLINE noWebGL2RenderingContext #-}
gTypeWebGL2RenderingContext :: JSM GType
gTypeWebGL2RenderingContext = GType . Object <$> jsg "WebGL2RenderingContext"
newtype WebGLActiveInfo = WebGLActiveInfo { unWebGLActiveInfo :: JSVal }
instance PToJSVal WebGLActiveInfo where
pToJSVal = unWebGLActiveInfo
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLActiveInfo where
pFromJSVal = WebGLActiveInfo
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLActiveInfo where
toJSVal = return . unWebGLActiveInfo
{-# INLINE toJSVal #-}
instance FromJSVal WebGLActiveInfo where
fromJSVal v = fmap WebGLActiveInfo <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLActiveInfo
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLActiveInfo where
makeObject = makeObject . unWebGLActiveInfo
instance IsGObject WebGLActiveInfo where
typeGType _ = gTypeWebGLActiveInfo
{-# INLINE typeGType #-}
noWebGLActiveInfo :: Maybe WebGLActiveInfo
noWebGLActiveInfo = Nothing
{-# INLINE noWebGLActiveInfo #-}
gTypeWebGLActiveInfo :: JSM GType
gTypeWebGLActiveInfo = GType . Object <$> jsg "WebGLActiveInfo"
newtype WebGLBuffer = WebGLBuffer { unWebGLBuffer :: JSVal }
instance PToJSVal WebGLBuffer where
pToJSVal = unWebGLBuffer
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLBuffer where
pFromJSVal = WebGLBuffer
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLBuffer where
toJSVal = return . unWebGLBuffer
{-# INLINE toJSVal #-}
instance FromJSVal WebGLBuffer where
fromJSVal v = fmap WebGLBuffer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLBuffer
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLBuffer where
makeObject = makeObject . unWebGLBuffer
instance IsGObject WebGLBuffer where
typeGType _ = gTypeWebGLBuffer
{-# INLINE typeGType #-}
noWebGLBuffer :: Maybe WebGLBuffer
noWebGLBuffer = Nothing
{-# INLINE noWebGLBuffer #-}
gTypeWebGLBuffer :: JSM GType
gTypeWebGLBuffer = GType . Object <$> jsg "WebGLBuffer"
newtype WebGLCompressedTextureATC = WebGLCompressedTextureATC { unWebGLCompressedTextureATC :: JSVal }
instance PToJSVal WebGLCompressedTextureATC where
pToJSVal = unWebGLCompressedTextureATC
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLCompressedTextureATC where
pFromJSVal = WebGLCompressedTextureATC
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLCompressedTextureATC where
toJSVal = return . unWebGLCompressedTextureATC
{-# INLINE toJSVal #-}
instance FromJSVal WebGLCompressedTextureATC where
fromJSVal v = fmap WebGLCompressedTextureATC <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLCompressedTextureATC
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLCompressedTextureATC where
makeObject = makeObject . unWebGLCompressedTextureATC
instance IsGObject WebGLCompressedTextureATC where
typeGType _ = gTypeWebGLCompressedTextureATC
{-# INLINE typeGType #-}
noWebGLCompressedTextureATC :: Maybe WebGLCompressedTextureATC
noWebGLCompressedTextureATC = Nothing
{-# INLINE noWebGLCompressedTextureATC #-}
gTypeWebGLCompressedTextureATC :: JSM GType
gTypeWebGLCompressedTextureATC = GType . Object <$> jsg "WebGLCompressedTextureATC"
newtype WebGLCompressedTexturePVRTC = WebGLCompressedTexturePVRTC { unWebGLCompressedTexturePVRTC :: JSVal }
instance PToJSVal WebGLCompressedTexturePVRTC where
pToJSVal = unWebGLCompressedTexturePVRTC
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLCompressedTexturePVRTC where
pFromJSVal = WebGLCompressedTexturePVRTC
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLCompressedTexturePVRTC where
toJSVal = return . unWebGLCompressedTexturePVRTC
{-# INLINE toJSVal #-}
instance FromJSVal WebGLCompressedTexturePVRTC where
fromJSVal v = fmap WebGLCompressedTexturePVRTC <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLCompressedTexturePVRTC
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLCompressedTexturePVRTC where
makeObject = makeObject . unWebGLCompressedTexturePVRTC
instance IsGObject WebGLCompressedTexturePVRTC where
typeGType _ = gTypeWebGLCompressedTexturePVRTC
{-# INLINE typeGType #-}
noWebGLCompressedTexturePVRTC :: Maybe WebGLCompressedTexturePVRTC
noWebGLCompressedTexturePVRTC = Nothing
{-# INLINE noWebGLCompressedTexturePVRTC #-}
gTypeWebGLCompressedTexturePVRTC :: JSM GType
gTypeWebGLCompressedTexturePVRTC = GType . Object <$> jsg "WebGLCompressedTexturePVRTC"
newtype WebGLCompressedTextureS3TC = WebGLCompressedTextureS3TC { unWebGLCompressedTextureS3TC :: JSVal }
instance PToJSVal WebGLCompressedTextureS3TC where
pToJSVal = unWebGLCompressedTextureS3TC
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLCompressedTextureS3TC where
pFromJSVal = WebGLCompressedTextureS3TC
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLCompressedTextureS3TC where
toJSVal = return . unWebGLCompressedTextureS3TC
{-# INLINE toJSVal #-}
instance FromJSVal WebGLCompressedTextureS3TC where
fromJSVal v = fmap WebGLCompressedTextureS3TC <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLCompressedTextureS3TC
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLCompressedTextureS3TC where
makeObject = makeObject . unWebGLCompressedTextureS3TC
instance IsGObject WebGLCompressedTextureS3TC where
typeGType _ = gTypeWebGLCompressedTextureS3TC
{-# INLINE typeGType #-}
noWebGLCompressedTextureS3TC :: Maybe WebGLCompressedTextureS3TC
noWebGLCompressedTextureS3TC = Nothing
{-# INLINE noWebGLCompressedTextureS3TC #-}
gTypeWebGLCompressedTextureS3TC :: JSM GType
gTypeWebGLCompressedTextureS3TC = GType . Object <$> jsg "WebGLCompressedTextureS3TC"
newtype WebGLContextAttributes = WebGLContextAttributes { unWebGLContextAttributes :: JSVal }
instance PToJSVal WebGLContextAttributes where
pToJSVal = unWebGLContextAttributes
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLContextAttributes where
pFromJSVal = WebGLContextAttributes
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLContextAttributes where
toJSVal = return . unWebGLContextAttributes
{-# INLINE toJSVal #-}
instance FromJSVal WebGLContextAttributes where
fromJSVal v = fmap WebGLContextAttributes <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLContextAttributes
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLContextAttributes where
makeObject = makeObject . unWebGLContextAttributes
instance IsGObject WebGLContextAttributes where
typeGType _ = gTypeWebGLContextAttributes
{-# INLINE typeGType #-}
noWebGLContextAttributes :: Maybe WebGLContextAttributes
noWebGLContextAttributes = Nothing
{-# INLINE noWebGLContextAttributes #-}
gTypeWebGLContextAttributes :: JSM GType
gTypeWebGLContextAttributes = GType . Object <$> jsg "WebGLContextAttributes"
newtype WebGLContextEvent = WebGLContextEvent { unWebGLContextEvent :: JSVal }
instance PToJSVal WebGLContextEvent where
pToJSVal = unWebGLContextEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLContextEvent where
pFromJSVal = WebGLContextEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLContextEvent where
toJSVal = return . unWebGLContextEvent
{-# INLINE toJSVal #-}
instance FromJSVal WebGLContextEvent where
fromJSVal v = fmap WebGLContextEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLContextEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLContextEvent where
makeObject = makeObject . unWebGLContextEvent
instance IsEvent WebGLContextEvent
instance IsGObject WebGLContextEvent where
typeGType _ = gTypeWebGLContextEvent
{-# INLINE typeGType #-}
noWebGLContextEvent :: Maybe WebGLContextEvent
noWebGLContextEvent = Nothing
{-# INLINE noWebGLContextEvent #-}
gTypeWebGLContextEvent :: JSM GType
gTypeWebGLContextEvent = GType . Object <$> jsg "WebGLContextEvent"
newtype WebGLContextEventInit = WebGLContextEventInit { unWebGLContextEventInit :: JSVal }
instance PToJSVal WebGLContextEventInit where
pToJSVal = unWebGLContextEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLContextEventInit where
pFromJSVal = WebGLContextEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLContextEventInit where
toJSVal = return . unWebGLContextEventInit
{-# INLINE toJSVal #-}
instance FromJSVal WebGLContextEventInit where
fromJSVal v = fmap WebGLContextEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLContextEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLContextEventInit where
makeObject = makeObject . unWebGLContextEventInit
instance IsEventInit WebGLContextEventInit
instance IsGObject WebGLContextEventInit where
typeGType _ = gTypeWebGLContextEventInit
{-# INLINE typeGType #-}
noWebGLContextEventInit :: Maybe WebGLContextEventInit
noWebGLContextEventInit = Nothing
{-# INLINE noWebGLContextEventInit #-}
gTypeWebGLContextEventInit :: JSM GType
gTypeWebGLContextEventInit = GType . Object <$> jsg "WebGLContextEventInit"
newtype WebGLDebugRendererInfo = WebGLDebugRendererInfo { unWebGLDebugRendererInfo :: JSVal }
instance PToJSVal WebGLDebugRendererInfo where
pToJSVal = unWebGLDebugRendererInfo
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLDebugRendererInfo where
pFromJSVal = WebGLDebugRendererInfo
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLDebugRendererInfo where
toJSVal = return . unWebGLDebugRendererInfo
{-# INLINE toJSVal #-}
instance FromJSVal WebGLDebugRendererInfo where
fromJSVal v = fmap WebGLDebugRendererInfo <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLDebugRendererInfo
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLDebugRendererInfo where
makeObject = makeObject . unWebGLDebugRendererInfo
instance IsGObject WebGLDebugRendererInfo where
typeGType _ = gTypeWebGLDebugRendererInfo
{-# INLINE typeGType #-}
noWebGLDebugRendererInfo :: Maybe WebGLDebugRendererInfo
noWebGLDebugRendererInfo = Nothing
{-# INLINE noWebGLDebugRendererInfo #-}
gTypeWebGLDebugRendererInfo :: JSM GType
gTypeWebGLDebugRendererInfo = GType . Object <$> jsg "WebGLDebugRendererInfo"
newtype WebGLDebugShaders = WebGLDebugShaders { unWebGLDebugShaders :: JSVal }
instance PToJSVal WebGLDebugShaders where
pToJSVal = unWebGLDebugShaders
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLDebugShaders where
pFromJSVal = WebGLDebugShaders
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLDebugShaders where
toJSVal = return . unWebGLDebugShaders
{-# INLINE toJSVal #-}
instance FromJSVal WebGLDebugShaders where
fromJSVal v = fmap WebGLDebugShaders <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLDebugShaders
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLDebugShaders where
makeObject = makeObject . unWebGLDebugShaders
instance IsGObject WebGLDebugShaders where
typeGType _ = gTypeWebGLDebugShaders
{-# INLINE typeGType #-}
noWebGLDebugShaders :: Maybe WebGLDebugShaders
noWebGLDebugShaders = Nothing
{-# INLINE noWebGLDebugShaders #-}
gTypeWebGLDebugShaders :: JSM GType
gTypeWebGLDebugShaders = GType . Object <$> jsg "WebGLDebugShaders"
newtype WebGLDepthTexture = WebGLDepthTexture { unWebGLDepthTexture :: JSVal }
instance PToJSVal WebGLDepthTexture where
pToJSVal = unWebGLDepthTexture
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLDepthTexture where
pFromJSVal = WebGLDepthTexture
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLDepthTexture where
toJSVal = return . unWebGLDepthTexture
{-# INLINE toJSVal #-}
instance FromJSVal WebGLDepthTexture where
fromJSVal v = fmap WebGLDepthTexture <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLDepthTexture
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLDepthTexture where
makeObject = makeObject . unWebGLDepthTexture
instance IsGObject WebGLDepthTexture where
typeGType _ = gTypeWebGLDepthTexture
{-# INLINE typeGType #-}
noWebGLDepthTexture :: Maybe WebGLDepthTexture
noWebGLDepthTexture = Nothing
{-# INLINE noWebGLDepthTexture #-}
gTypeWebGLDepthTexture :: JSM GType
gTypeWebGLDepthTexture = GType . Object <$> jsg "WebGLDepthTexture"
newtype WebGLDrawBuffers = WebGLDrawBuffers { unWebGLDrawBuffers :: JSVal }
instance PToJSVal WebGLDrawBuffers where
pToJSVal = unWebGLDrawBuffers
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLDrawBuffers where
pFromJSVal = WebGLDrawBuffers
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLDrawBuffers where
toJSVal = return . unWebGLDrawBuffers
{-# INLINE toJSVal #-}
instance FromJSVal WebGLDrawBuffers where
fromJSVal v = fmap WebGLDrawBuffers <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLDrawBuffers
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLDrawBuffers where
makeObject = makeObject . unWebGLDrawBuffers
instance IsGObject WebGLDrawBuffers where
typeGType _ = gTypeWebGLDrawBuffers
{-# INLINE typeGType #-}
noWebGLDrawBuffers :: Maybe WebGLDrawBuffers
noWebGLDrawBuffers = Nothing
{-# INLINE noWebGLDrawBuffers #-}
gTypeWebGLDrawBuffers :: JSM GType
gTypeWebGLDrawBuffers = GType . Object <$> jsg "WebGLDrawBuffers"
newtype WebGLFramebuffer = WebGLFramebuffer { unWebGLFramebuffer :: JSVal }
instance PToJSVal WebGLFramebuffer where
pToJSVal = unWebGLFramebuffer
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLFramebuffer where
pFromJSVal = WebGLFramebuffer
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLFramebuffer where
toJSVal = return . unWebGLFramebuffer
{-# INLINE toJSVal #-}
instance FromJSVal WebGLFramebuffer where
fromJSVal v = fmap WebGLFramebuffer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLFramebuffer
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLFramebuffer where
makeObject = makeObject . unWebGLFramebuffer
instance IsGObject WebGLFramebuffer where
typeGType _ = gTypeWebGLFramebuffer
{-# INLINE typeGType #-}
noWebGLFramebuffer :: Maybe WebGLFramebuffer
noWebGLFramebuffer = Nothing
{-# INLINE noWebGLFramebuffer #-}
gTypeWebGLFramebuffer :: JSM GType
gTypeWebGLFramebuffer = GType . Object <$> jsg "WebGLFramebuffer"
newtype WebGLLoseContext = WebGLLoseContext { unWebGLLoseContext :: JSVal }
instance PToJSVal WebGLLoseContext where
pToJSVal = unWebGLLoseContext
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLLoseContext where
pFromJSVal = WebGLLoseContext
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLLoseContext where
toJSVal = return . unWebGLLoseContext
{-# INLINE toJSVal #-}
instance FromJSVal WebGLLoseContext where
fromJSVal v = fmap WebGLLoseContext <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLLoseContext
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLLoseContext where
makeObject = makeObject . unWebGLLoseContext
instance IsGObject WebGLLoseContext where
typeGType _ = gTypeWebGLLoseContext
{-# INLINE typeGType #-}
noWebGLLoseContext :: Maybe WebGLLoseContext
noWebGLLoseContext = Nothing
{-# INLINE noWebGLLoseContext #-}
gTypeWebGLLoseContext :: JSM GType
gTypeWebGLLoseContext = GType . Object <$> jsg "WebGLLoseContext"
newtype WebGLProgram = WebGLProgram { unWebGLProgram :: JSVal }
instance PToJSVal WebGLProgram where
pToJSVal = unWebGLProgram
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLProgram where
pFromJSVal = WebGLProgram
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLProgram where
toJSVal = return . unWebGLProgram
{-# INLINE toJSVal #-}
instance FromJSVal WebGLProgram where
fromJSVal v = fmap WebGLProgram <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLProgram
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLProgram where
makeObject = makeObject . unWebGLProgram
instance IsGObject WebGLProgram where
typeGType _ = gTypeWebGLProgram
{-# INLINE typeGType #-}
noWebGLProgram :: Maybe WebGLProgram
noWebGLProgram = Nothing
{-# INLINE noWebGLProgram #-}
gTypeWebGLProgram :: JSM GType
gTypeWebGLProgram = GType . Object <$> jsg "WebGLProgram"
newtype WebGLQuery = WebGLQuery { unWebGLQuery :: JSVal }
instance PToJSVal WebGLQuery where
pToJSVal = unWebGLQuery
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLQuery where
pFromJSVal = WebGLQuery
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLQuery where
toJSVal = return . unWebGLQuery
{-# INLINE toJSVal #-}
instance FromJSVal WebGLQuery where
fromJSVal v = fmap WebGLQuery <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLQuery
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLQuery where
makeObject = makeObject . unWebGLQuery
instance IsGObject WebGLQuery where
typeGType _ = gTypeWebGLQuery
{-# INLINE typeGType #-}
noWebGLQuery :: Maybe WebGLQuery
noWebGLQuery = Nothing
{-# INLINE noWebGLQuery #-}
gTypeWebGLQuery :: JSM GType
gTypeWebGLQuery = GType . Object <$> jsg "WebGLQuery"
newtype WebGLRenderbuffer = WebGLRenderbuffer { unWebGLRenderbuffer :: JSVal }
instance PToJSVal WebGLRenderbuffer where
pToJSVal = unWebGLRenderbuffer
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLRenderbuffer where
pFromJSVal = WebGLRenderbuffer
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLRenderbuffer where
toJSVal = return . unWebGLRenderbuffer
{-# INLINE toJSVal #-}
instance FromJSVal WebGLRenderbuffer where
fromJSVal v = fmap WebGLRenderbuffer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLRenderbuffer
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLRenderbuffer where
makeObject = makeObject . unWebGLRenderbuffer
instance IsGObject WebGLRenderbuffer where
typeGType _ = gTypeWebGLRenderbuffer
{-# INLINE typeGType #-}
noWebGLRenderbuffer :: Maybe WebGLRenderbuffer
noWebGLRenderbuffer = Nothing
{-# INLINE noWebGLRenderbuffer #-}
gTypeWebGLRenderbuffer :: JSM GType
gTypeWebGLRenderbuffer = GType . Object <$> jsg "WebGLRenderbuffer"
newtype WebGLRenderingContext = WebGLRenderingContext { unWebGLRenderingContext :: JSVal }
instance PToJSVal WebGLRenderingContext where
pToJSVal = unWebGLRenderingContext
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLRenderingContext where
pFromJSVal = WebGLRenderingContext
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLRenderingContext where
toJSVal = return . unWebGLRenderingContext
{-# INLINE toJSVal #-}
instance FromJSVal WebGLRenderingContext where
fromJSVal v = fmap WebGLRenderingContext <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLRenderingContext
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLRenderingContext where
makeObject = makeObject . unWebGLRenderingContext
instance IsWebGLRenderingContextBase WebGLRenderingContext
instance IsGObject WebGLRenderingContext where
typeGType _ = gTypeWebGLRenderingContext
{-# INLINE typeGType #-}
noWebGLRenderingContext :: Maybe WebGLRenderingContext
noWebGLRenderingContext = Nothing
{-# INLINE noWebGLRenderingContext #-}
gTypeWebGLRenderingContext :: JSM GType
gTypeWebGLRenderingContext = GType . Object <$> jsg "WebGLRenderingContext"
newtype WebGLRenderingContextBase = WebGLRenderingContextBase { unWebGLRenderingContextBase :: JSVal }
instance PToJSVal WebGLRenderingContextBase where
pToJSVal = unWebGLRenderingContextBase
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLRenderingContextBase where
pFromJSVal = WebGLRenderingContextBase
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLRenderingContextBase where
toJSVal = return . unWebGLRenderingContextBase
{-# INLINE toJSVal #-}
instance FromJSVal WebGLRenderingContextBase where
fromJSVal v = fmap WebGLRenderingContextBase <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLRenderingContextBase
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLRenderingContextBase where
makeObject = makeObject . unWebGLRenderingContextBase
class (IsGObject o) => IsWebGLRenderingContextBase o
toWebGLRenderingContextBase :: IsWebGLRenderingContextBase o => o -> WebGLRenderingContextBase
toWebGLRenderingContextBase = WebGLRenderingContextBase . coerce
instance IsWebGLRenderingContextBase WebGLRenderingContextBase
instance IsGObject WebGLRenderingContextBase where
typeGType _ = gTypeWebGLRenderingContextBase
{-# INLINE typeGType #-}
noWebGLRenderingContextBase :: Maybe WebGLRenderingContextBase
noWebGLRenderingContextBase = Nothing
{-# INLINE noWebGLRenderingContextBase #-}
gTypeWebGLRenderingContextBase :: JSM GType
gTypeWebGLRenderingContextBase = GType . Object <$> jsg "WebGLRenderingContextBase"
newtype WebGLSampler = WebGLSampler { unWebGLSampler :: JSVal }
instance PToJSVal WebGLSampler where
pToJSVal = unWebGLSampler
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLSampler where
pFromJSVal = WebGLSampler
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLSampler where
toJSVal = return . unWebGLSampler
{-# INLINE toJSVal #-}
instance FromJSVal WebGLSampler where
fromJSVal v = fmap WebGLSampler <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLSampler
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLSampler where
makeObject = makeObject . unWebGLSampler
instance IsGObject WebGLSampler where
typeGType _ = gTypeWebGLSampler
{-# INLINE typeGType #-}
noWebGLSampler :: Maybe WebGLSampler
noWebGLSampler = Nothing
{-# INLINE noWebGLSampler #-}
gTypeWebGLSampler :: JSM GType
gTypeWebGLSampler = GType . Object <$> jsg "WebGLSampler"
newtype WebGLShader = WebGLShader { unWebGLShader :: JSVal }
instance PToJSVal WebGLShader where
pToJSVal = unWebGLShader
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLShader where
pFromJSVal = WebGLShader
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLShader where
toJSVal = return . unWebGLShader
{-# INLINE toJSVal #-}
instance FromJSVal WebGLShader where
fromJSVal v = fmap WebGLShader <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLShader
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLShader where
makeObject = makeObject . unWebGLShader
instance IsGObject WebGLShader where
typeGType _ = gTypeWebGLShader
{-# INLINE typeGType #-}
noWebGLShader :: Maybe WebGLShader
noWebGLShader = Nothing
{-# INLINE noWebGLShader #-}
gTypeWebGLShader :: JSM GType
gTypeWebGLShader = GType . Object <$> jsg "WebGLShader"
newtype WebGLShaderPrecisionFormat = WebGLShaderPrecisionFormat { unWebGLShaderPrecisionFormat :: JSVal }
instance PToJSVal WebGLShaderPrecisionFormat where
pToJSVal = unWebGLShaderPrecisionFormat
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLShaderPrecisionFormat where
pFromJSVal = WebGLShaderPrecisionFormat
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLShaderPrecisionFormat where
toJSVal = return . unWebGLShaderPrecisionFormat
{-# INLINE toJSVal #-}
instance FromJSVal WebGLShaderPrecisionFormat where
fromJSVal v = fmap WebGLShaderPrecisionFormat <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLShaderPrecisionFormat
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLShaderPrecisionFormat where
makeObject = makeObject . unWebGLShaderPrecisionFormat
instance IsGObject WebGLShaderPrecisionFormat where
typeGType _ = gTypeWebGLShaderPrecisionFormat
{-# INLINE typeGType #-}
noWebGLShaderPrecisionFormat :: Maybe WebGLShaderPrecisionFormat
noWebGLShaderPrecisionFormat = Nothing
{-# INLINE noWebGLShaderPrecisionFormat #-}
gTypeWebGLShaderPrecisionFormat :: JSM GType
gTypeWebGLShaderPrecisionFormat = GType . Object <$> jsg "WebGLShaderPrecisionFormat"
newtype WebGLSync = WebGLSync { unWebGLSync :: JSVal }
instance PToJSVal WebGLSync where
pToJSVal = unWebGLSync
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLSync where
pFromJSVal = WebGLSync
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLSync where
toJSVal = return . unWebGLSync
{-# INLINE toJSVal #-}
instance FromJSVal WebGLSync where
fromJSVal v = fmap WebGLSync <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLSync
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLSync where
makeObject = makeObject . unWebGLSync
instance IsGObject WebGLSync where
typeGType _ = gTypeWebGLSync
{-# INLINE typeGType #-}
noWebGLSync :: Maybe WebGLSync
noWebGLSync = Nothing
{-# INLINE noWebGLSync #-}
gTypeWebGLSync :: JSM GType
gTypeWebGLSync = GType . Object <$> jsg "WebGLSync"
newtype WebGLTexture = WebGLTexture { unWebGLTexture :: JSVal }
instance PToJSVal WebGLTexture where
pToJSVal = unWebGLTexture
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLTexture where
pFromJSVal = WebGLTexture
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLTexture where
toJSVal = return . unWebGLTexture
{-# INLINE toJSVal #-}
instance FromJSVal WebGLTexture where
fromJSVal v = fmap WebGLTexture <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLTexture
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLTexture where
makeObject = makeObject . unWebGLTexture
instance IsGObject WebGLTexture where
typeGType _ = gTypeWebGLTexture
{-# INLINE typeGType #-}
noWebGLTexture :: Maybe WebGLTexture
noWebGLTexture = Nothing
{-# INLINE noWebGLTexture #-}
gTypeWebGLTexture :: JSM GType
gTypeWebGLTexture = GType . Object <$> jsg "WebGLTexture"
newtype WebGLTransformFeedback = WebGLTransformFeedback { unWebGLTransformFeedback :: JSVal }
instance PToJSVal WebGLTransformFeedback where
pToJSVal = unWebGLTransformFeedback
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLTransformFeedback where
pFromJSVal = WebGLTransformFeedback
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLTransformFeedback where
toJSVal = return . unWebGLTransformFeedback
{-# INLINE toJSVal #-}
instance FromJSVal WebGLTransformFeedback where
fromJSVal v = fmap WebGLTransformFeedback <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLTransformFeedback
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLTransformFeedback where
makeObject = makeObject . unWebGLTransformFeedback
instance IsGObject WebGLTransformFeedback where
typeGType _ = gTypeWebGLTransformFeedback
{-# INLINE typeGType #-}
noWebGLTransformFeedback :: Maybe WebGLTransformFeedback
noWebGLTransformFeedback = Nothing
{-# INLINE noWebGLTransformFeedback #-}
gTypeWebGLTransformFeedback :: JSM GType
gTypeWebGLTransformFeedback = GType . Object <$> jsg "WebGLTransformFeedback"
newtype WebGLUniformLocation = WebGLUniformLocation { unWebGLUniformLocation :: JSVal }
instance PToJSVal WebGLUniformLocation where
pToJSVal = unWebGLUniformLocation
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLUniformLocation where
pFromJSVal = WebGLUniformLocation
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLUniformLocation where
toJSVal = return . unWebGLUniformLocation
{-# INLINE toJSVal #-}
instance FromJSVal WebGLUniformLocation where
fromJSVal v = fmap WebGLUniformLocation <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLUniformLocation
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLUniformLocation where
makeObject = makeObject . unWebGLUniformLocation
instance IsGObject WebGLUniformLocation where
typeGType _ = gTypeWebGLUniformLocation
{-# INLINE typeGType #-}
noWebGLUniformLocation :: Maybe WebGLUniformLocation
noWebGLUniformLocation = Nothing
{-# INLINE noWebGLUniformLocation #-}
gTypeWebGLUniformLocation :: JSM GType
gTypeWebGLUniformLocation = GType . Object <$> jsg "WebGLUniformLocation"
newtype WebGLVertexArrayObject = WebGLVertexArrayObject { unWebGLVertexArrayObject :: JSVal }
instance PToJSVal WebGLVertexArrayObject where
pToJSVal = unWebGLVertexArrayObject
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLVertexArrayObject where
pFromJSVal = WebGLVertexArrayObject
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLVertexArrayObject where
toJSVal = return . unWebGLVertexArrayObject
{-# INLINE toJSVal #-}
instance FromJSVal WebGLVertexArrayObject where
fromJSVal v = fmap WebGLVertexArrayObject <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLVertexArrayObject
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLVertexArrayObject where
makeObject = makeObject . unWebGLVertexArrayObject
instance IsGObject WebGLVertexArrayObject where
typeGType _ = gTypeWebGLVertexArrayObject
{-# INLINE typeGType #-}
noWebGLVertexArrayObject :: Maybe WebGLVertexArrayObject
noWebGLVertexArrayObject = Nothing
{-# INLINE noWebGLVertexArrayObject #-}
gTypeWebGLVertexArrayObject :: JSM GType
gTypeWebGLVertexArrayObject = GType . Object <$> jsg "WebGLVertexArrayObject"
newtype WebGLVertexArrayObjectOES = WebGLVertexArrayObjectOES { unWebGLVertexArrayObjectOES :: JSVal }
instance PToJSVal WebGLVertexArrayObjectOES where
pToJSVal = unWebGLVertexArrayObjectOES
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGLVertexArrayObjectOES where
pFromJSVal = WebGLVertexArrayObjectOES
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGLVertexArrayObjectOES where
toJSVal = return . unWebGLVertexArrayObjectOES
{-# INLINE toJSVal #-}
instance FromJSVal WebGLVertexArrayObjectOES where
fromJSVal v = fmap WebGLVertexArrayObjectOES <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGLVertexArrayObjectOES
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGLVertexArrayObjectOES where
makeObject = makeObject . unWebGLVertexArrayObjectOES
instance IsGObject WebGLVertexArrayObjectOES where
typeGType _ = gTypeWebGLVertexArrayObjectOES
{-# INLINE typeGType #-}
noWebGLVertexArrayObjectOES :: Maybe WebGLVertexArrayObjectOES
noWebGLVertexArrayObjectOES = Nothing
{-# INLINE noWebGLVertexArrayObjectOES #-}
gTypeWebGLVertexArrayObjectOES :: JSM GType
gTypeWebGLVertexArrayObjectOES = GType . Object <$> jsg "WebGLVertexArrayObjectOES"
newtype WebGPUBuffer = WebGPUBuffer { unWebGPUBuffer :: JSVal }
instance PToJSVal WebGPUBuffer where
pToJSVal = unWebGPUBuffer
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUBuffer where
pFromJSVal = WebGPUBuffer
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUBuffer where
toJSVal = return . unWebGPUBuffer
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUBuffer where
fromJSVal v = fmap WebGPUBuffer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUBuffer
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUBuffer where
makeObject = makeObject . unWebGPUBuffer
instance IsGObject WebGPUBuffer where
typeGType _ = gTypeWebGPUBuffer
{-# INLINE typeGType #-}
noWebGPUBuffer :: Maybe WebGPUBuffer
noWebGPUBuffer = Nothing
{-# INLINE noWebGPUBuffer #-}
gTypeWebGPUBuffer :: JSM GType
gTypeWebGPUBuffer = GType . Object <$> jsg "WebGPUBuffer"
newtype WebGPUCommandBuffer = WebGPUCommandBuffer { unWebGPUCommandBuffer :: JSVal }
instance PToJSVal WebGPUCommandBuffer where
pToJSVal = unWebGPUCommandBuffer
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUCommandBuffer where
pFromJSVal = WebGPUCommandBuffer
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUCommandBuffer where
toJSVal = return . unWebGPUCommandBuffer
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUCommandBuffer where
fromJSVal v = fmap WebGPUCommandBuffer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUCommandBuffer
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUCommandBuffer where
makeObject = makeObject . unWebGPUCommandBuffer
instance IsGObject WebGPUCommandBuffer where
typeGType _ = gTypeWebGPUCommandBuffer
{-# INLINE typeGType #-}
noWebGPUCommandBuffer :: Maybe WebGPUCommandBuffer
noWebGPUCommandBuffer = Nothing
{-# INLINE noWebGPUCommandBuffer #-}
gTypeWebGPUCommandBuffer :: JSM GType
gTypeWebGPUCommandBuffer = GType . Object <$> jsg "WebGPUCommandBuffer"
newtype WebGPUCommandQueue = WebGPUCommandQueue { unWebGPUCommandQueue :: JSVal }
instance PToJSVal WebGPUCommandQueue where
pToJSVal = unWebGPUCommandQueue
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUCommandQueue where
pFromJSVal = WebGPUCommandQueue
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUCommandQueue where
toJSVal = return . unWebGPUCommandQueue
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUCommandQueue where
fromJSVal v = fmap WebGPUCommandQueue <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUCommandQueue
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUCommandQueue where
makeObject = makeObject . unWebGPUCommandQueue
instance IsGObject WebGPUCommandQueue where
typeGType _ = gTypeWebGPUCommandQueue
{-# INLINE typeGType #-}
noWebGPUCommandQueue :: Maybe WebGPUCommandQueue
noWebGPUCommandQueue = Nothing
{-# INLINE noWebGPUCommandQueue #-}
gTypeWebGPUCommandQueue :: JSM GType
gTypeWebGPUCommandQueue = GType . Object <$> jsg "WebGPUCommandQueue"
newtype WebGPUComputeCommandEncoder = WebGPUComputeCommandEncoder { unWebGPUComputeCommandEncoder :: JSVal }
instance PToJSVal WebGPUComputeCommandEncoder where
pToJSVal = unWebGPUComputeCommandEncoder
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUComputeCommandEncoder where
pFromJSVal = WebGPUComputeCommandEncoder
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUComputeCommandEncoder where
toJSVal = return . unWebGPUComputeCommandEncoder
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUComputeCommandEncoder where
fromJSVal v = fmap WebGPUComputeCommandEncoder <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUComputeCommandEncoder
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUComputeCommandEncoder where
makeObject = makeObject . unWebGPUComputeCommandEncoder
instance IsGObject WebGPUComputeCommandEncoder where
typeGType _ = gTypeWebGPUComputeCommandEncoder
{-# INLINE typeGType #-}
noWebGPUComputeCommandEncoder :: Maybe WebGPUComputeCommandEncoder
noWebGPUComputeCommandEncoder = Nothing
{-# INLINE noWebGPUComputeCommandEncoder #-}
gTypeWebGPUComputeCommandEncoder :: JSM GType
gTypeWebGPUComputeCommandEncoder = GType . Object <$> jsg "WebGPUComputeCommandEncoder"
newtype WebGPUComputePipelineState = WebGPUComputePipelineState { unWebGPUComputePipelineState :: JSVal }
instance PToJSVal WebGPUComputePipelineState where
pToJSVal = unWebGPUComputePipelineState
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUComputePipelineState where
pFromJSVal = WebGPUComputePipelineState
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUComputePipelineState where
toJSVal = return . unWebGPUComputePipelineState
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUComputePipelineState where
fromJSVal v = fmap WebGPUComputePipelineState <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUComputePipelineState
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUComputePipelineState where
makeObject = makeObject . unWebGPUComputePipelineState
instance IsGObject WebGPUComputePipelineState where
typeGType _ = gTypeWebGPUComputePipelineState
{-# INLINE typeGType #-}
noWebGPUComputePipelineState :: Maybe WebGPUComputePipelineState
noWebGPUComputePipelineState = Nothing
{-# INLINE noWebGPUComputePipelineState #-}
gTypeWebGPUComputePipelineState :: JSM GType
gTypeWebGPUComputePipelineState = GType . Object <$> jsg "WebGPUComputePipelineState"
newtype WebGPUDepthStencilDescriptor = WebGPUDepthStencilDescriptor { unWebGPUDepthStencilDescriptor :: JSVal }
instance PToJSVal WebGPUDepthStencilDescriptor where
pToJSVal = unWebGPUDepthStencilDescriptor
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUDepthStencilDescriptor where
pFromJSVal = WebGPUDepthStencilDescriptor
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUDepthStencilDescriptor where
toJSVal = return . unWebGPUDepthStencilDescriptor
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUDepthStencilDescriptor where
fromJSVal v = fmap WebGPUDepthStencilDescriptor <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUDepthStencilDescriptor
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUDepthStencilDescriptor where
makeObject = makeObject . unWebGPUDepthStencilDescriptor
instance IsGObject WebGPUDepthStencilDescriptor where
typeGType _ = gTypeWebGPUDepthStencilDescriptor
{-# INLINE typeGType #-}
noWebGPUDepthStencilDescriptor :: Maybe WebGPUDepthStencilDescriptor
noWebGPUDepthStencilDescriptor = Nothing
{-# INLINE noWebGPUDepthStencilDescriptor #-}
gTypeWebGPUDepthStencilDescriptor :: JSM GType
gTypeWebGPUDepthStencilDescriptor = GType . Object <$> jsg "WebGPUDepthStencilDescriptor"
newtype WebGPUDepthStencilState = WebGPUDepthStencilState { unWebGPUDepthStencilState :: JSVal }
instance PToJSVal WebGPUDepthStencilState where
pToJSVal = unWebGPUDepthStencilState
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUDepthStencilState where
pFromJSVal = WebGPUDepthStencilState
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUDepthStencilState where
toJSVal = return . unWebGPUDepthStencilState
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUDepthStencilState where
fromJSVal v = fmap WebGPUDepthStencilState <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUDepthStencilState
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUDepthStencilState where
makeObject = makeObject . unWebGPUDepthStencilState
instance IsGObject WebGPUDepthStencilState where
typeGType _ = gTypeWebGPUDepthStencilState
{-# INLINE typeGType #-}
noWebGPUDepthStencilState :: Maybe WebGPUDepthStencilState
noWebGPUDepthStencilState = Nothing
{-# INLINE noWebGPUDepthStencilState #-}
gTypeWebGPUDepthStencilState :: JSM GType
gTypeWebGPUDepthStencilState = GType . Object <$> jsg "WebGPUDepthStencilState"
newtype WebGPUDrawable = WebGPUDrawable { unWebGPUDrawable :: JSVal }
instance PToJSVal WebGPUDrawable where
pToJSVal = unWebGPUDrawable
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUDrawable where
pFromJSVal = WebGPUDrawable
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUDrawable where
toJSVal = return . unWebGPUDrawable
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUDrawable where
fromJSVal v = fmap WebGPUDrawable <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUDrawable
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUDrawable where
makeObject = makeObject . unWebGPUDrawable
instance IsGObject WebGPUDrawable where
typeGType _ = gTypeWebGPUDrawable
{-# INLINE typeGType #-}
noWebGPUDrawable :: Maybe WebGPUDrawable
noWebGPUDrawable = Nothing
{-# INLINE noWebGPUDrawable #-}
gTypeWebGPUDrawable :: JSM GType
gTypeWebGPUDrawable = GType . Object <$> jsg "WebGPUDrawable"
newtype WebGPUFunction = WebGPUFunction { unWebGPUFunction :: JSVal }
instance PToJSVal WebGPUFunction where
pToJSVal = unWebGPUFunction
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUFunction where
pFromJSVal = WebGPUFunction
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUFunction where
toJSVal = return . unWebGPUFunction
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUFunction where
fromJSVal v = fmap WebGPUFunction <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUFunction
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUFunction where
makeObject = makeObject . unWebGPUFunction
instance IsGObject WebGPUFunction where
typeGType _ = gTypeWebGPUFunction
{-# INLINE typeGType #-}
noWebGPUFunction :: Maybe WebGPUFunction
noWebGPUFunction = Nothing
{-# INLINE noWebGPUFunction #-}
gTypeWebGPUFunction :: JSM GType
gTypeWebGPUFunction = GType . Object <$> jsg "WebGPUFunction"
newtype WebGPULibrary = WebGPULibrary { unWebGPULibrary :: JSVal }
instance PToJSVal WebGPULibrary where
pToJSVal = unWebGPULibrary
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPULibrary where
pFromJSVal = WebGPULibrary
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPULibrary where
toJSVal = return . unWebGPULibrary
{-# INLINE toJSVal #-}
instance FromJSVal WebGPULibrary where
fromJSVal v = fmap WebGPULibrary <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPULibrary
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPULibrary where
makeObject = makeObject . unWebGPULibrary
instance IsGObject WebGPULibrary where
typeGType _ = gTypeWebGPULibrary
{-# INLINE typeGType #-}
noWebGPULibrary :: Maybe WebGPULibrary
noWebGPULibrary = Nothing
{-# INLINE noWebGPULibrary #-}
gTypeWebGPULibrary :: JSM GType
gTypeWebGPULibrary = GType . Object <$> jsg "WebGPULibrary"
newtype WebGPURenderCommandEncoder = WebGPURenderCommandEncoder { unWebGPURenderCommandEncoder :: JSVal }
instance PToJSVal WebGPURenderCommandEncoder where
pToJSVal = unWebGPURenderCommandEncoder
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPURenderCommandEncoder where
pFromJSVal = WebGPURenderCommandEncoder
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPURenderCommandEncoder where
toJSVal = return . unWebGPURenderCommandEncoder
{-# INLINE toJSVal #-}
instance FromJSVal WebGPURenderCommandEncoder where
fromJSVal v = fmap WebGPURenderCommandEncoder <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPURenderCommandEncoder
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPURenderCommandEncoder where
makeObject = makeObject . unWebGPURenderCommandEncoder
instance IsGObject WebGPURenderCommandEncoder where
typeGType _ = gTypeWebGPURenderCommandEncoder
{-# INLINE typeGType #-}
noWebGPURenderCommandEncoder :: Maybe WebGPURenderCommandEncoder
noWebGPURenderCommandEncoder = Nothing
{-# INLINE noWebGPURenderCommandEncoder #-}
gTypeWebGPURenderCommandEncoder :: JSM GType
gTypeWebGPURenderCommandEncoder = GType . Object <$> jsg "WebGPURenderCommandEncoder"
newtype WebGPURenderPassAttachmentDescriptor = WebGPURenderPassAttachmentDescriptor { unWebGPURenderPassAttachmentDescriptor :: JSVal }
instance PToJSVal WebGPURenderPassAttachmentDescriptor where
pToJSVal = unWebGPURenderPassAttachmentDescriptor
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPURenderPassAttachmentDescriptor where
pFromJSVal = WebGPURenderPassAttachmentDescriptor
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPURenderPassAttachmentDescriptor where
toJSVal = return . unWebGPURenderPassAttachmentDescriptor
{-# INLINE toJSVal #-}
instance FromJSVal WebGPURenderPassAttachmentDescriptor where
fromJSVal v = fmap WebGPURenderPassAttachmentDescriptor <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPURenderPassAttachmentDescriptor
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPURenderPassAttachmentDescriptor where
makeObject = makeObject . unWebGPURenderPassAttachmentDescriptor
class (IsGObject o) => IsWebGPURenderPassAttachmentDescriptor o
toWebGPURenderPassAttachmentDescriptor :: IsWebGPURenderPassAttachmentDescriptor o => o -> WebGPURenderPassAttachmentDescriptor
toWebGPURenderPassAttachmentDescriptor = WebGPURenderPassAttachmentDescriptor . coerce
instance IsWebGPURenderPassAttachmentDescriptor WebGPURenderPassAttachmentDescriptor
instance IsGObject WebGPURenderPassAttachmentDescriptor where
typeGType _ = gTypeWebGPURenderPassAttachmentDescriptor
{-# INLINE typeGType #-}
noWebGPURenderPassAttachmentDescriptor :: Maybe WebGPURenderPassAttachmentDescriptor
noWebGPURenderPassAttachmentDescriptor = Nothing
{-# INLINE noWebGPURenderPassAttachmentDescriptor #-}
gTypeWebGPURenderPassAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPassAttachmentDescriptor = GType . Object <$> jsg "WebGPURenderPassAttachmentDescriptor"
newtype WebGPURenderPassColorAttachmentDescriptor = WebGPURenderPassColorAttachmentDescriptor { unWebGPURenderPassColorAttachmentDescriptor :: JSVal }
instance PToJSVal WebGPURenderPassColorAttachmentDescriptor where
pToJSVal = unWebGPURenderPassColorAttachmentDescriptor
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPURenderPassColorAttachmentDescriptor where
pFromJSVal = WebGPURenderPassColorAttachmentDescriptor
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPURenderPassColorAttachmentDescriptor where
toJSVal = return . unWebGPURenderPassColorAttachmentDescriptor
{-# INLINE toJSVal #-}
instance FromJSVal WebGPURenderPassColorAttachmentDescriptor where
fromJSVal v = fmap WebGPURenderPassColorAttachmentDescriptor <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPURenderPassColorAttachmentDescriptor
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPURenderPassColorAttachmentDescriptor where
makeObject = makeObject . unWebGPURenderPassColorAttachmentDescriptor
instance IsWebGPURenderPassAttachmentDescriptor WebGPURenderPassColorAttachmentDescriptor
instance IsGObject WebGPURenderPassColorAttachmentDescriptor where
typeGType _ = gTypeWebGPURenderPassColorAttachmentDescriptor
{-# INLINE typeGType #-}
noWebGPURenderPassColorAttachmentDescriptor :: Maybe WebGPURenderPassColorAttachmentDescriptor
noWebGPURenderPassColorAttachmentDescriptor = Nothing
{-# INLINE noWebGPURenderPassColorAttachmentDescriptor #-}
gTypeWebGPURenderPassColorAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPassColorAttachmentDescriptor = GType . Object <$> jsg "WebGPURenderPassColorAttachmentDescriptor"
newtype WebGPURenderPassDepthAttachmentDescriptor = WebGPURenderPassDepthAttachmentDescriptor { unWebGPURenderPassDepthAttachmentDescriptor :: JSVal }
instance PToJSVal WebGPURenderPassDepthAttachmentDescriptor where
pToJSVal = unWebGPURenderPassDepthAttachmentDescriptor
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPURenderPassDepthAttachmentDescriptor where
pFromJSVal = WebGPURenderPassDepthAttachmentDescriptor
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPURenderPassDepthAttachmentDescriptor where
toJSVal = return . unWebGPURenderPassDepthAttachmentDescriptor
{-# INLINE toJSVal #-}
instance FromJSVal WebGPURenderPassDepthAttachmentDescriptor where
fromJSVal v = fmap WebGPURenderPassDepthAttachmentDescriptor <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPURenderPassDepthAttachmentDescriptor
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPURenderPassDepthAttachmentDescriptor where
makeObject = makeObject . unWebGPURenderPassDepthAttachmentDescriptor
instance IsWebGPURenderPassAttachmentDescriptor WebGPURenderPassDepthAttachmentDescriptor
instance IsGObject WebGPURenderPassDepthAttachmentDescriptor where
typeGType _ = gTypeWebGPURenderPassDepthAttachmentDescriptor
{-# INLINE typeGType #-}
noWebGPURenderPassDepthAttachmentDescriptor :: Maybe WebGPURenderPassDepthAttachmentDescriptor
noWebGPURenderPassDepthAttachmentDescriptor = Nothing
{-# INLINE noWebGPURenderPassDepthAttachmentDescriptor #-}
gTypeWebGPURenderPassDepthAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPassDepthAttachmentDescriptor = GType . Object <$> jsg "WebGPURenderPassDepthAttachmentDescriptor"
newtype WebGPURenderPassDescriptor = WebGPURenderPassDescriptor { unWebGPURenderPassDescriptor :: JSVal }
instance PToJSVal WebGPURenderPassDescriptor where
pToJSVal = unWebGPURenderPassDescriptor
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPURenderPassDescriptor where
pFromJSVal = WebGPURenderPassDescriptor
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPURenderPassDescriptor where
toJSVal = return . unWebGPURenderPassDescriptor
{-# INLINE toJSVal #-}
instance FromJSVal WebGPURenderPassDescriptor where
fromJSVal v = fmap WebGPURenderPassDescriptor <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPURenderPassDescriptor
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPURenderPassDescriptor where
makeObject = makeObject . unWebGPURenderPassDescriptor
instance IsGObject WebGPURenderPassDescriptor where
typeGType _ = gTypeWebGPURenderPassDescriptor
{-# INLINE typeGType #-}
noWebGPURenderPassDescriptor :: Maybe WebGPURenderPassDescriptor
noWebGPURenderPassDescriptor = Nothing
{-# INLINE noWebGPURenderPassDescriptor #-}
gTypeWebGPURenderPassDescriptor :: JSM GType
gTypeWebGPURenderPassDescriptor = GType . Object <$> jsg "WebGPURenderPassDescriptor"
newtype WebGPURenderPipelineColorAttachmentDescriptor = WebGPURenderPipelineColorAttachmentDescriptor { unWebGPURenderPipelineColorAttachmentDescriptor :: JSVal }
instance PToJSVal WebGPURenderPipelineColorAttachmentDescriptor where
pToJSVal = unWebGPURenderPipelineColorAttachmentDescriptor
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPURenderPipelineColorAttachmentDescriptor where
pFromJSVal = WebGPURenderPipelineColorAttachmentDescriptor
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPURenderPipelineColorAttachmentDescriptor where
toJSVal = return . unWebGPURenderPipelineColorAttachmentDescriptor
{-# INLINE toJSVal #-}
instance FromJSVal WebGPURenderPipelineColorAttachmentDescriptor where
fromJSVal v = fmap WebGPURenderPipelineColorAttachmentDescriptor <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPURenderPipelineColorAttachmentDescriptor
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPURenderPipelineColorAttachmentDescriptor where
makeObject = makeObject . unWebGPURenderPipelineColorAttachmentDescriptor
instance IsGObject WebGPURenderPipelineColorAttachmentDescriptor where
typeGType _ = gTypeWebGPURenderPipelineColorAttachmentDescriptor
{-# INLINE typeGType #-}
noWebGPURenderPipelineColorAttachmentDescriptor :: Maybe WebGPURenderPipelineColorAttachmentDescriptor
noWebGPURenderPipelineColorAttachmentDescriptor = Nothing
{-# INLINE noWebGPURenderPipelineColorAttachmentDescriptor #-}
gTypeWebGPURenderPipelineColorAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPipelineColorAttachmentDescriptor = GType . Object <$> jsg "WebGPURenderPipelineColorAttachmentDescriptor"
newtype WebGPURenderPipelineDescriptor = WebGPURenderPipelineDescriptor { unWebGPURenderPipelineDescriptor :: JSVal }
instance PToJSVal WebGPURenderPipelineDescriptor where
pToJSVal = unWebGPURenderPipelineDescriptor
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPURenderPipelineDescriptor where
pFromJSVal = WebGPURenderPipelineDescriptor
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPURenderPipelineDescriptor where
toJSVal = return . unWebGPURenderPipelineDescriptor
{-# INLINE toJSVal #-}
instance FromJSVal WebGPURenderPipelineDescriptor where
fromJSVal v = fmap WebGPURenderPipelineDescriptor <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPURenderPipelineDescriptor
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPURenderPipelineDescriptor where
makeObject = makeObject . unWebGPURenderPipelineDescriptor
instance IsGObject WebGPURenderPipelineDescriptor where
typeGType _ = gTypeWebGPURenderPipelineDescriptor
{-# INLINE typeGType #-}
noWebGPURenderPipelineDescriptor :: Maybe WebGPURenderPipelineDescriptor
noWebGPURenderPipelineDescriptor = Nothing
{-# INLINE noWebGPURenderPipelineDescriptor #-}
gTypeWebGPURenderPipelineDescriptor :: JSM GType
gTypeWebGPURenderPipelineDescriptor = GType . Object <$> jsg "WebGPURenderPipelineDescriptor"
newtype WebGPURenderPipelineState = WebGPURenderPipelineState { unWebGPURenderPipelineState :: JSVal }
instance PToJSVal WebGPURenderPipelineState where
pToJSVal = unWebGPURenderPipelineState
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPURenderPipelineState where
pFromJSVal = WebGPURenderPipelineState
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPURenderPipelineState where
toJSVal = return . unWebGPURenderPipelineState
{-# INLINE toJSVal #-}
instance FromJSVal WebGPURenderPipelineState where
fromJSVal v = fmap WebGPURenderPipelineState <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPURenderPipelineState
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPURenderPipelineState where
makeObject = makeObject . unWebGPURenderPipelineState
instance IsGObject WebGPURenderPipelineState where
typeGType _ = gTypeWebGPURenderPipelineState
{-# INLINE typeGType #-}
noWebGPURenderPipelineState :: Maybe WebGPURenderPipelineState
noWebGPURenderPipelineState = Nothing
{-# INLINE noWebGPURenderPipelineState #-}
gTypeWebGPURenderPipelineState :: JSM GType
gTypeWebGPURenderPipelineState = GType . Object <$> jsg "WebGPURenderPipelineState"
newtype WebGPURenderingContext = WebGPURenderingContext { unWebGPURenderingContext :: JSVal }
instance PToJSVal WebGPURenderingContext where
pToJSVal = unWebGPURenderingContext
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPURenderingContext where
pFromJSVal = WebGPURenderingContext
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPURenderingContext where
toJSVal = return . unWebGPURenderingContext
{-# INLINE toJSVal #-}
instance FromJSVal WebGPURenderingContext where
fromJSVal v = fmap WebGPURenderingContext <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPURenderingContext
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPURenderingContext where
makeObject = makeObject . unWebGPURenderingContext
instance IsGObject WebGPURenderingContext where
typeGType _ = gTypeWebGPURenderingContext
{-# INLINE typeGType #-}
noWebGPURenderingContext :: Maybe WebGPURenderingContext
noWebGPURenderingContext = Nothing
{-# INLINE noWebGPURenderingContext #-}
gTypeWebGPURenderingContext :: JSM GType
gTypeWebGPURenderingContext = GType . Object <$> jsg "WebGPURenderingContext"
newtype WebGPUSize = WebGPUSize { unWebGPUSize :: JSVal }
instance PToJSVal WebGPUSize where
pToJSVal = unWebGPUSize
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUSize where
pFromJSVal = WebGPUSize
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUSize where
toJSVal = return . unWebGPUSize
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUSize where
fromJSVal v = fmap WebGPUSize <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUSize
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUSize where
makeObject = makeObject . unWebGPUSize
instance IsGObject WebGPUSize where
typeGType _ = gTypeWebGPUSize
{-# INLINE typeGType #-}
noWebGPUSize :: Maybe WebGPUSize
noWebGPUSize = Nothing
{-# INLINE noWebGPUSize #-}
gTypeWebGPUSize :: JSM GType
gTypeWebGPUSize = GType . Object <$> jsg "WebGPUSize"
newtype WebGPUTexture = WebGPUTexture { unWebGPUTexture :: JSVal }
instance PToJSVal WebGPUTexture where
pToJSVal = unWebGPUTexture
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUTexture where
pFromJSVal = WebGPUTexture
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUTexture where
toJSVal = return . unWebGPUTexture
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUTexture where
fromJSVal v = fmap WebGPUTexture <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUTexture
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUTexture where
makeObject = makeObject . unWebGPUTexture
instance IsGObject WebGPUTexture where
typeGType _ = gTypeWebGPUTexture
{-# INLINE typeGType #-}
noWebGPUTexture :: Maybe WebGPUTexture
noWebGPUTexture = Nothing
{-# INLINE noWebGPUTexture #-}
gTypeWebGPUTexture :: JSM GType
gTypeWebGPUTexture = GType . Object <$> jsg "WebGPUTexture"
newtype WebGPUTextureDescriptor = WebGPUTextureDescriptor { unWebGPUTextureDescriptor :: JSVal }
instance PToJSVal WebGPUTextureDescriptor where
pToJSVal = unWebGPUTextureDescriptor
{-# INLINE pToJSVal #-}
instance PFromJSVal WebGPUTextureDescriptor where
pFromJSVal = WebGPUTextureDescriptor
{-# INLINE pFromJSVal #-}
instance ToJSVal WebGPUTextureDescriptor where
toJSVal = return . unWebGPUTextureDescriptor
{-# INLINE toJSVal #-}
instance FromJSVal WebGPUTextureDescriptor where
fromJSVal v = fmap WebGPUTextureDescriptor <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebGPUTextureDescriptor
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebGPUTextureDescriptor where
makeObject = makeObject . unWebGPUTextureDescriptor
instance IsGObject WebGPUTextureDescriptor where
typeGType _ = gTypeWebGPUTextureDescriptor
{-# INLINE typeGType #-}
noWebGPUTextureDescriptor :: Maybe WebGPUTextureDescriptor
noWebGPUTextureDescriptor = Nothing
{-# INLINE noWebGPUTextureDescriptor #-}
gTypeWebGPUTextureDescriptor :: JSM GType
gTypeWebGPUTextureDescriptor = GType . Object <$> jsg "WebGPUTextureDescriptor"
newtype WebKitAnimationEvent = WebKitAnimationEvent { unWebKitAnimationEvent :: JSVal }
instance PToJSVal WebKitAnimationEvent where
pToJSVal = unWebKitAnimationEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitAnimationEvent where
pFromJSVal = WebKitAnimationEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitAnimationEvent where
toJSVal = return . unWebKitAnimationEvent
{-# INLINE toJSVal #-}
instance FromJSVal WebKitAnimationEvent where
fromJSVal v = fmap WebKitAnimationEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitAnimationEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitAnimationEvent where
makeObject = makeObject . unWebKitAnimationEvent
instance IsEvent WebKitAnimationEvent
instance IsGObject WebKitAnimationEvent where
typeGType _ = gTypeWebKitAnimationEvent
{-# INLINE typeGType #-}
noWebKitAnimationEvent :: Maybe WebKitAnimationEvent
noWebKitAnimationEvent = Nothing
{-# INLINE noWebKitAnimationEvent #-}
gTypeWebKitAnimationEvent :: JSM GType
gTypeWebKitAnimationEvent = GType . Object <$> jsg "WebKitAnimationEvent"
newtype WebKitAnimationEventInit = WebKitAnimationEventInit { unWebKitAnimationEventInit :: JSVal }
instance PToJSVal WebKitAnimationEventInit where
pToJSVal = unWebKitAnimationEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitAnimationEventInit where
pFromJSVal = WebKitAnimationEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitAnimationEventInit where
toJSVal = return . unWebKitAnimationEventInit
{-# INLINE toJSVal #-}
instance FromJSVal WebKitAnimationEventInit where
fromJSVal v = fmap WebKitAnimationEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitAnimationEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitAnimationEventInit where
makeObject = makeObject . unWebKitAnimationEventInit
instance IsEventInit WebKitAnimationEventInit
instance IsGObject WebKitAnimationEventInit where
typeGType _ = gTypeWebKitAnimationEventInit
{-# INLINE typeGType #-}
noWebKitAnimationEventInit :: Maybe WebKitAnimationEventInit
noWebKitAnimationEventInit = Nothing
{-# INLINE noWebKitAnimationEventInit #-}
gTypeWebKitAnimationEventInit :: JSM GType
gTypeWebKitAnimationEventInit = GType . Object <$> jsg "WebKitAnimationEventInit"
newtype WebKitCSSMatrix = WebKitCSSMatrix { unWebKitCSSMatrix :: JSVal }
instance PToJSVal WebKitCSSMatrix where
pToJSVal = unWebKitCSSMatrix
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitCSSMatrix where
pFromJSVal = WebKitCSSMatrix
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitCSSMatrix where
toJSVal = return . unWebKitCSSMatrix
{-# INLINE toJSVal #-}
instance FromJSVal WebKitCSSMatrix where
fromJSVal v = fmap WebKitCSSMatrix <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitCSSMatrix
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitCSSMatrix where
makeObject = makeObject . unWebKitCSSMatrix
instance IsGObject WebKitCSSMatrix where
typeGType _ = gTypeWebKitCSSMatrix
{-# INLINE typeGType #-}
noWebKitCSSMatrix :: Maybe WebKitCSSMatrix
noWebKitCSSMatrix = Nothing
{-# INLINE noWebKitCSSMatrix #-}
gTypeWebKitCSSMatrix :: JSM GType
gTypeWebKitCSSMatrix = GType . Object <$> jsg "WebKitCSSMatrix"
newtype WebKitCSSRegionRule = WebKitCSSRegionRule { unWebKitCSSRegionRule :: JSVal }
instance PToJSVal WebKitCSSRegionRule where
pToJSVal = unWebKitCSSRegionRule
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitCSSRegionRule where
pFromJSVal = WebKitCSSRegionRule
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitCSSRegionRule where
toJSVal = return . unWebKitCSSRegionRule
{-# INLINE toJSVal #-}
instance FromJSVal WebKitCSSRegionRule where
fromJSVal v = fmap WebKitCSSRegionRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitCSSRegionRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitCSSRegionRule where
makeObject = makeObject . unWebKitCSSRegionRule
instance IsCSSRule WebKitCSSRegionRule
instance IsGObject WebKitCSSRegionRule where
typeGType _ = gTypeWebKitCSSRegionRule
{-# INLINE typeGType #-}
noWebKitCSSRegionRule :: Maybe WebKitCSSRegionRule
noWebKitCSSRegionRule = Nothing
{-# INLINE noWebKitCSSRegionRule #-}
gTypeWebKitCSSRegionRule :: JSM GType
gTypeWebKitCSSRegionRule = GType . Object <$> jsg "WebKitCSSRegionRule"
newtype WebKitCSSViewportRule = WebKitCSSViewportRule { unWebKitCSSViewportRule :: JSVal }
instance PToJSVal WebKitCSSViewportRule where
pToJSVal = unWebKitCSSViewportRule
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitCSSViewportRule where
pFromJSVal = WebKitCSSViewportRule
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitCSSViewportRule where
toJSVal = return . unWebKitCSSViewportRule
{-# INLINE toJSVal #-}
instance FromJSVal WebKitCSSViewportRule where
fromJSVal v = fmap WebKitCSSViewportRule <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitCSSViewportRule
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitCSSViewportRule where
makeObject = makeObject . unWebKitCSSViewportRule
instance IsCSSRule WebKitCSSViewportRule
instance IsGObject WebKitCSSViewportRule where
typeGType _ = gTypeWebKitCSSViewportRule
{-# INLINE typeGType #-}
noWebKitCSSViewportRule :: Maybe WebKitCSSViewportRule
noWebKitCSSViewportRule = Nothing
{-# INLINE noWebKitCSSViewportRule #-}
gTypeWebKitCSSViewportRule :: JSM GType
gTypeWebKitCSSViewportRule = GType . Object <$> jsg "WebKitCSSViewportRule"
newtype WebKitMediaKeyError = WebKitMediaKeyError { unWebKitMediaKeyError :: JSVal }
instance PToJSVal WebKitMediaKeyError where
pToJSVal = unWebKitMediaKeyError
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitMediaKeyError where
pFromJSVal = WebKitMediaKeyError
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitMediaKeyError where
toJSVal = return . unWebKitMediaKeyError
{-# INLINE toJSVal #-}
instance FromJSVal WebKitMediaKeyError where
fromJSVal v = fmap WebKitMediaKeyError <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitMediaKeyError
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitMediaKeyError where
makeObject = makeObject . unWebKitMediaKeyError
instance IsGObject WebKitMediaKeyError where
typeGType _ = gTypeWebKitMediaKeyError
{-# INLINE typeGType #-}
noWebKitMediaKeyError :: Maybe WebKitMediaKeyError
noWebKitMediaKeyError = Nothing
{-# INLINE noWebKitMediaKeyError #-}
gTypeWebKitMediaKeyError :: JSM GType
gTypeWebKitMediaKeyError = GType . Object <$> jsg "WebKitMediaKeyError"
newtype WebKitMediaKeyMessageEvent = WebKitMediaKeyMessageEvent { unWebKitMediaKeyMessageEvent :: JSVal }
instance PToJSVal WebKitMediaKeyMessageEvent where
pToJSVal = unWebKitMediaKeyMessageEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitMediaKeyMessageEvent where
pFromJSVal = WebKitMediaKeyMessageEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitMediaKeyMessageEvent where
toJSVal = return . unWebKitMediaKeyMessageEvent
{-# INLINE toJSVal #-}
instance FromJSVal WebKitMediaKeyMessageEvent where
fromJSVal v = fmap WebKitMediaKeyMessageEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitMediaKeyMessageEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitMediaKeyMessageEvent where
makeObject = makeObject . unWebKitMediaKeyMessageEvent
instance IsEvent WebKitMediaKeyMessageEvent
instance IsGObject WebKitMediaKeyMessageEvent where
typeGType _ = gTypeWebKitMediaKeyMessageEvent
{-# INLINE typeGType #-}
noWebKitMediaKeyMessageEvent :: Maybe WebKitMediaKeyMessageEvent
noWebKitMediaKeyMessageEvent = Nothing
{-# INLINE noWebKitMediaKeyMessageEvent #-}
gTypeWebKitMediaKeyMessageEvent :: JSM GType
gTypeWebKitMediaKeyMessageEvent = GType . Object <$> jsg "WebKitMediaKeyMessageEvent"
newtype WebKitMediaKeyMessageEventInit = WebKitMediaKeyMessageEventInit { unWebKitMediaKeyMessageEventInit :: JSVal }
instance PToJSVal WebKitMediaKeyMessageEventInit where
pToJSVal = unWebKitMediaKeyMessageEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitMediaKeyMessageEventInit where
pFromJSVal = WebKitMediaKeyMessageEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitMediaKeyMessageEventInit where
toJSVal = return . unWebKitMediaKeyMessageEventInit
{-# INLINE toJSVal #-}
instance FromJSVal WebKitMediaKeyMessageEventInit where
fromJSVal v = fmap WebKitMediaKeyMessageEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitMediaKeyMessageEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitMediaKeyMessageEventInit where
makeObject = makeObject . unWebKitMediaKeyMessageEventInit
instance IsEventInit WebKitMediaKeyMessageEventInit
instance IsGObject WebKitMediaKeyMessageEventInit where
typeGType _ = gTypeWebKitMediaKeyMessageEventInit
{-# INLINE typeGType #-}
noWebKitMediaKeyMessageEventInit :: Maybe WebKitMediaKeyMessageEventInit
noWebKitMediaKeyMessageEventInit = Nothing
{-# INLINE noWebKitMediaKeyMessageEventInit #-}
gTypeWebKitMediaKeyMessageEventInit :: JSM GType
gTypeWebKitMediaKeyMessageEventInit = GType . Object <$> jsg "WebKitMediaKeyMessageEventInit"
newtype WebKitMediaKeyNeededEvent = WebKitMediaKeyNeededEvent { unWebKitMediaKeyNeededEvent :: JSVal }
instance PToJSVal WebKitMediaKeyNeededEvent where
pToJSVal = unWebKitMediaKeyNeededEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitMediaKeyNeededEvent where
pFromJSVal = WebKitMediaKeyNeededEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitMediaKeyNeededEvent where
toJSVal = return . unWebKitMediaKeyNeededEvent
{-# INLINE toJSVal #-}
instance FromJSVal WebKitMediaKeyNeededEvent where
fromJSVal v = fmap WebKitMediaKeyNeededEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitMediaKeyNeededEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitMediaKeyNeededEvent where
makeObject = makeObject . unWebKitMediaKeyNeededEvent
instance IsEvent WebKitMediaKeyNeededEvent
instance IsGObject WebKitMediaKeyNeededEvent where
typeGType _ = gTypeWebKitMediaKeyNeededEvent
{-# INLINE typeGType #-}
noWebKitMediaKeyNeededEvent :: Maybe WebKitMediaKeyNeededEvent
noWebKitMediaKeyNeededEvent = Nothing
{-# INLINE noWebKitMediaKeyNeededEvent #-}
gTypeWebKitMediaKeyNeededEvent :: JSM GType
gTypeWebKitMediaKeyNeededEvent = GType . Object <$> jsg "WebKitMediaKeyNeededEvent"
newtype WebKitMediaKeyNeededEventInit = WebKitMediaKeyNeededEventInit { unWebKitMediaKeyNeededEventInit :: JSVal }
instance PToJSVal WebKitMediaKeyNeededEventInit where
pToJSVal = unWebKitMediaKeyNeededEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitMediaKeyNeededEventInit where
pFromJSVal = WebKitMediaKeyNeededEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitMediaKeyNeededEventInit where
toJSVal = return . unWebKitMediaKeyNeededEventInit
{-# INLINE toJSVal #-}
instance FromJSVal WebKitMediaKeyNeededEventInit where
fromJSVal v = fmap WebKitMediaKeyNeededEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitMediaKeyNeededEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitMediaKeyNeededEventInit where
makeObject = makeObject . unWebKitMediaKeyNeededEventInit
instance IsEventInit WebKitMediaKeyNeededEventInit
instance IsGObject WebKitMediaKeyNeededEventInit where
typeGType _ = gTypeWebKitMediaKeyNeededEventInit
{-# INLINE typeGType #-}
noWebKitMediaKeyNeededEventInit :: Maybe WebKitMediaKeyNeededEventInit
noWebKitMediaKeyNeededEventInit = Nothing
{-# INLINE noWebKitMediaKeyNeededEventInit #-}
gTypeWebKitMediaKeyNeededEventInit :: JSM GType
gTypeWebKitMediaKeyNeededEventInit = GType . Object <$> jsg "WebKitMediaKeyNeededEventInit"
newtype WebKitMediaKeySession = WebKitMediaKeySession { unWebKitMediaKeySession :: JSVal }
instance PToJSVal WebKitMediaKeySession where
pToJSVal = unWebKitMediaKeySession
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitMediaKeySession where
pFromJSVal = WebKitMediaKeySession
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitMediaKeySession where
toJSVal = return . unWebKitMediaKeySession
{-# INLINE toJSVal #-}
instance FromJSVal WebKitMediaKeySession where
fromJSVal v = fmap WebKitMediaKeySession <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitMediaKeySession
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitMediaKeySession where
makeObject = makeObject . unWebKitMediaKeySession
instance IsEventTarget WebKitMediaKeySession
instance IsGObject WebKitMediaKeySession where
typeGType _ = gTypeWebKitMediaKeySession
{-# INLINE typeGType #-}
noWebKitMediaKeySession :: Maybe WebKitMediaKeySession
noWebKitMediaKeySession = Nothing
{-# INLINE noWebKitMediaKeySession #-}
gTypeWebKitMediaKeySession :: JSM GType
gTypeWebKitMediaKeySession = GType . Object <$> jsg "WebKitMediaKeySession"
newtype WebKitMediaKeys = WebKitMediaKeys { unWebKitMediaKeys :: JSVal }
instance PToJSVal WebKitMediaKeys where
pToJSVal = unWebKitMediaKeys
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitMediaKeys where
pFromJSVal = WebKitMediaKeys
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitMediaKeys where
toJSVal = return . unWebKitMediaKeys
{-# INLINE toJSVal #-}
instance FromJSVal WebKitMediaKeys where
fromJSVal v = fmap WebKitMediaKeys <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitMediaKeys
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitMediaKeys where
makeObject = makeObject . unWebKitMediaKeys
instance IsGObject WebKitMediaKeys where
typeGType _ = gTypeWebKitMediaKeys
{-# INLINE typeGType #-}
noWebKitMediaKeys :: Maybe WebKitMediaKeys
noWebKitMediaKeys = Nothing
{-# INLINE noWebKitMediaKeys #-}
gTypeWebKitMediaKeys :: JSM GType
gTypeWebKitMediaKeys = GType . Object <$> jsg "WebKitMediaKeys"
newtype WebKitNamedFlow = WebKitNamedFlow { unWebKitNamedFlow :: JSVal }
instance PToJSVal WebKitNamedFlow where
pToJSVal = unWebKitNamedFlow
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitNamedFlow where
pFromJSVal = WebKitNamedFlow
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitNamedFlow where
toJSVal = return . unWebKitNamedFlow
{-# INLINE toJSVal #-}
instance FromJSVal WebKitNamedFlow where
fromJSVal v = fmap WebKitNamedFlow <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitNamedFlow
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitNamedFlow where
makeObject = makeObject . unWebKitNamedFlow
instance IsEventTarget WebKitNamedFlow
instance IsGObject WebKitNamedFlow where
typeGType _ = gTypeWebKitNamedFlow
{-# INLINE typeGType #-}
noWebKitNamedFlow :: Maybe WebKitNamedFlow
noWebKitNamedFlow = Nothing
{-# INLINE noWebKitNamedFlow #-}
gTypeWebKitNamedFlow :: JSM GType
gTypeWebKitNamedFlow = GType . Object <$> jsg "WebKitNamedFlow"
newtype WebKitNamespace = WebKitNamespace { unWebKitNamespace :: JSVal }
instance PToJSVal WebKitNamespace where
pToJSVal = unWebKitNamespace
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitNamespace where
pFromJSVal = WebKitNamespace
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitNamespace where
toJSVal = return . unWebKitNamespace
{-# INLINE toJSVal #-}
instance FromJSVal WebKitNamespace where
fromJSVal v = fmap WebKitNamespace <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitNamespace
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitNamespace where
makeObject = makeObject . unWebKitNamespace
instance IsGObject WebKitNamespace where
typeGType _ = gTypeWebKitNamespace
{-# INLINE typeGType #-}
noWebKitNamespace :: Maybe WebKitNamespace
noWebKitNamespace = Nothing
{-# INLINE noWebKitNamespace #-}
gTypeWebKitNamespace :: JSM GType
gTypeWebKitNamespace = GType . Object <$> jsg "WebKitNamespace"
newtype WebKitPlaybackTargetAvailabilityEvent = WebKitPlaybackTargetAvailabilityEvent { unWebKitPlaybackTargetAvailabilityEvent :: JSVal }
instance PToJSVal WebKitPlaybackTargetAvailabilityEvent where
pToJSVal = unWebKitPlaybackTargetAvailabilityEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitPlaybackTargetAvailabilityEvent where
pFromJSVal = WebKitPlaybackTargetAvailabilityEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitPlaybackTargetAvailabilityEvent where
toJSVal = return . unWebKitPlaybackTargetAvailabilityEvent
{-# INLINE toJSVal #-}
instance FromJSVal WebKitPlaybackTargetAvailabilityEvent where
fromJSVal v = fmap WebKitPlaybackTargetAvailabilityEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitPlaybackTargetAvailabilityEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitPlaybackTargetAvailabilityEvent where
makeObject = makeObject . unWebKitPlaybackTargetAvailabilityEvent
instance IsEvent WebKitPlaybackTargetAvailabilityEvent
instance IsGObject WebKitPlaybackTargetAvailabilityEvent where
typeGType _ = gTypeWebKitPlaybackTargetAvailabilityEvent
{-# INLINE typeGType #-}
noWebKitPlaybackTargetAvailabilityEvent :: Maybe WebKitPlaybackTargetAvailabilityEvent
noWebKitPlaybackTargetAvailabilityEvent = Nothing
{-# INLINE noWebKitPlaybackTargetAvailabilityEvent #-}
gTypeWebKitPlaybackTargetAvailabilityEvent :: JSM GType
gTypeWebKitPlaybackTargetAvailabilityEvent = GType . Object <$> jsg "WebKitPlaybackTargetAvailabilityEvent"
newtype WebKitPlaybackTargetAvailabilityEventInit = WebKitPlaybackTargetAvailabilityEventInit { unWebKitPlaybackTargetAvailabilityEventInit :: JSVal }
instance PToJSVal WebKitPlaybackTargetAvailabilityEventInit where
pToJSVal = unWebKitPlaybackTargetAvailabilityEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitPlaybackTargetAvailabilityEventInit where
pFromJSVal = WebKitPlaybackTargetAvailabilityEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitPlaybackTargetAvailabilityEventInit where
toJSVal = return . unWebKitPlaybackTargetAvailabilityEventInit
{-# INLINE toJSVal #-}
instance FromJSVal WebKitPlaybackTargetAvailabilityEventInit where
fromJSVal v = fmap WebKitPlaybackTargetAvailabilityEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitPlaybackTargetAvailabilityEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitPlaybackTargetAvailabilityEventInit where
makeObject = makeObject . unWebKitPlaybackTargetAvailabilityEventInit
instance IsEventInit WebKitPlaybackTargetAvailabilityEventInit
instance IsGObject WebKitPlaybackTargetAvailabilityEventInit where
typeGType _ = gTypeWebKitPlaybackTargetAvailabilityEventInit
{-# INLINE typeGType #-}
noWebKitPlaybackTargetAvailabilityEventInit :: Maybe WebKitPlaybackTargetAvailabilityEventInit
noWebKitPlaybackTargetAvailabilityEventInit = Nothing
{-# INLINE noWebKitPlaybackTargetAvailabilityEventInit #-}
gTypeWebKitPlaybackTargetAvailabilityEventInit :: JSM GType
gTypeWebKitPlaybackTargetAvailabilityEventInit = GType . Object <$> jsg "WebKitPlaybackTargetAvailabilityEventInit"
newtype WebKitPoint = WebKitPoint { unWebKitPoint :: JSVal }
instance PToJSVal WebKitPoint where
pToJSVal = unWebKitPoint
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitPoint where
pFromJSVal = WebKitPoint
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitPoint where
toJSVal = return . unWebKitPoint
{-# INLINE toJSVal #-}
instance FromJSVal WebKitPoint where
fromJSVal v = fmap WebKitPoint <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitPoint
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitPoint where
makeObject = makeObject . unWebKitPoint
instance IsGObject WebKitPoint where
typeGType _ = gTypeWebKitPoint
{-# INLINE typeGType #-}
noWebKitPoint :: Maybe WebKitPoint
noWebKitPoint = Nothing
{-# INLINE noWebKitPoint #-}
gTypeWebKitPoint :: JSM GType
gTypeWebKitPoint = GType . Object <$> jsg "WebKitPoint"
newtype WebKitSubtleCrypto = WebKitSubtleCrypto { unWebKitSubtleCrypto :: JSVal }
instance PToJSVal WebKitSubtleCrypto where
pToJSVal = unWebKitSubtleCrypto
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitSubtleCrypto where
pFromJSVal = WebKitSubtleCrypto
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitSubtleCrypto where
toJSVal = return . unWebKitSubtleCrypto
{-# INLINE toJSVal #-}
instance FromJSVal WebKitSubtleCrypto where
fromJSVal v = fmap WebKitSubtleCrypto <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitSubtleCrypto
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitSubtleCrypto where
makeObject = makeObject . unWebKitSubtleCrypto
instance IsGObject WebKitSubtleCrypto where
typeGType _ = gTypeWebKitSubtleCrypto
{-# INLINE typeGType #-}
noWebKitSubtleCrypto :: Maybe WebKitSubtleCrypto
noWebKitSubtleCrypto = Nothing
{-# INLINE noWebKitSubtleCrypto #-}
gTypeWebKitSubtleCrypto :: JSM GType
gTypeWebKitSubtleCrypto = GType . Object <$> jsg "WebKitSubtleCrypto"
newtype WebKitTransitionEvent = WebKitTransitionEvent { unWebKitTransitionEvent :: JSVal }
instance PToJSVal WebKitTransitionEvent where
pToJSVal = unWebKitTransitionEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitTransitionEvent where
pFromJSVal = WebKitTransitionEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitTransitionEvent where
toJSVal = return . unWebKitTransitionEvent
{-# INLINE toJSVal #-}
instance FromJSVal WebKitTransitionEvent where
fromJSVal v = fmap WebKitTransitionEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitTransitionEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitTransitionEvent where
makeObject = makeObject . unWebKitTransitionEvent
instance IsEvent WebKitTransitionEvent
instance IsGObject WebKitTransitionEvent where
typeGType _ = gTypeWebKitTransitionEvent
{-# INLINE typeGType #-}
noWebKitTransitionEvent :: Maybe WebKitTransitionEvent
noWebKitTransitionEvent = Nothing
{-# INLINE noWebKitTransitionEvent #-}
gTypeWebKitTransitionEvent :: JSM GType
gTypeWebKitTransitionEvent = GType . Object <$> jsg "WebKitTransitionEvent"
newtype WebKitTransitionEventInit = WebKitTransitionEventInit { unWebKitTransitionEventInit :: JSVal }
instance PToJSVal WebKitTransitionEventInit where
pToJSVal = unWebKitTransitionEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal WebKitTransitionEventInit where
pFromJSVal = WebKitTransitionEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal WebKitTransitionEventInit where
toJSVal = return . unWebKitTransitionEventInit
{-# INLINE toJSVal #-}
instance FromJSVal WebKitTransitionEventInit where
fromJSVal v = fmap WebKitTransitionEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebKitTransitionEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebKitTransitionEventInit where
makeObject = makeObject . unWebKitTransitionEventInit
instance IsEventInit WebKitTransitionEventInit
instance IsGObject WebKitTransitionEventInit where
typeGType _ = gTypeWebKitTransitionEventInit
{-# INLINE typeGType #-}
noWebKitTransitionEventInit :: Maybe WebKitTransitionEventInit
noWebKitTransitionEventInit = Nothing
{-# INLINE noWebKitTransitionEventInit #-}
gTypeWebKitTransitionEventInit :: JSM GType
gTypeWebKitTransitionEventInit = GType . Object <$> jsg "WebKitTransitionEventInit"
newtype WebSocket = WebSocket { unWebSocket :: JSVal }
instance PToJSVal WebSocket where
pToJSVal = unWebSocket
{-# INLINE pToJSVal #-}
instance PFromJSVal WebSocket where
pFromJSVal = WebSocket
{-# INLINE pFromJSVal #-}
instance ToJSVal WebSocket where
toJSVal = return . unWebSocket
{-# INLINE toJSVal #-}
instance FromJSVal WebSocket where
fromJSVal v = fmap WebSocket <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WebSocket
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WebSocket where
makeObject = makeObject . unWebSocket
instance IsEventTarget WebSocket
instance IsGObject WebSocket where
typeGType _ = gTypeWebSocket
{-# INLINE typeGType #-}
noWebSocket :: Maybe WebSocket
noWebSocket = Nothing
{-# INLINE noWebSocket #-}
gTypeWebSocket :: JSM GType
gTypeWebSocket = GType . Object <$> jsg "WebSocket"
newtype WheelEvent = WheelEvent { unWheelEvent :: JSVal }
instance PToJSVal WheelEvent where
pToJSVal = unWheelEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal WheelEvent where
pFromJSVal = WheelEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal WheelEvent where
toJSVal = return . unWheelEvent
{-# INLINE toJSVal #-}
instance FromJSVal WheelEvent where
fromJSVal v = fmap WheelEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WheelEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WheelEvent where
makeObject = makeObject . unWheelEvent
instance IsMouseEvent WheelEvent
instance IsUIEvent WheelEvent
instance IsEvent WheelEvent
instance IsGObject WheelEvent where
typeGType _ = gTypeWheelEvent
{-# INLINE typeGType #-}
noWheelEvent :: Maybe WheelEvent
noWheelEvent = Nothing
{-# INLINE noWheelEvent #-}
gTypeWheelEvent :: JSM GType
gTypeWheelEvent = GType . Object <$> jsg "WheelEvent"
newtype WheelEventInit = WheelEventInit { unWheelEventInit :: JSVal }
instance PToJSVal WheelEventInit where
pToJSVal = unWheelEventInit
{-# INLINE pToJSVal #-}
instance PFromJSVal WheelEventInit where
pFromJSVal = WheelEventInit
{-# INLINE pFromJSVal #-}
instance ToJSVal WheelEventInit where
toJSVal = return . unWheelEventInit
{-# INLINE toJSVal #-}
instance FromJSVal WheelEventInit where
fromJSVal v = fmap WheelEventInit <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WheelEventInit
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WheelEventInit where
makeObject = makeObject . unWheelEventInit
instance IsMouseEventInit WheelEventInit
instance IsEventModifierInit WheelEventInit
instance IsUIEventInit WheelEventInit
instance IsEventInit WheelEventInit
instance IsGObject WheelEventInit where
typeGType _ = gTypeWheelEventInit
{-# INLINE typeGType #-}
noWheelEventInit :: Maybe WheelEventInit
noWheelEventInit = Nothing
{-# INLINE noWheelEventInit #-}
gTypeWheelEventInit :: JSM GType
gTypeWheelEventInit = GType . Object <$> jsg "WheelEventInit"
newtype Window = Window { unWindow :: JSVal }
instance PToJSVal Window where
pToJSVal = unWindow
{-# INLINE pToJSVal #-}
instance PFromJSVal Window where
pFromJSVal = Window
{-# INLINE pFromJSVal #-}
instance ToJSVal Window where
toJSVal = return . unWindow
{-# INLINE toJSVal #-}
instance FromJSVal Window where
fromJSVal v = fmap Window <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Window
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Window where
makeObject = makeObject . unWindow
instance IsEventTarget Window
instance IsWindowOrWorkerGlobalScope Window
instance IsWindowEventHandlers Window
instance IsGlobalPerformance Window
instance IsGlobalEventHandlers Window
instance IsGlobalCrypto Window
instance IsGObject Window where
typeGType _ = gTypeWindow
{-# INLINE typeGType #-}
noWindow :: Maybe Window
noWindow = Nothing
{-# INLINE noWindow #-}
gTypeWindow :: JSM GType
gTypeWindow = GType . Object <$> jsg "Window"
newtype WindowEventHandlers = WindowEventHandlers { unWindowEventHandlers :: JSVal }
instance PToJSVal WindowEventHandlers where
pToJSVal = unWindowEventHandlers
{-# INLINE pToJSVal #-}
instance PFromJSVal WindowEventHandlers where
pFromJSVal = WindowEventHandlers
{-# INLINE pFromJSVal #-}
instance ToJSVal WindowEventHandlers where
toJSVal = return . unWindowEventHandlers
{-# INLINE toJSVal #-}
instance FromJSVal WindowEventHandlers where
fromJSVal v = fmap WindowEventHandlers <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WindowEventHandlers
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WindowEventHandlers where
makeObject = makeObject . unWindowEventHandlers
class (IsGObject o) => IsWindowEventHandlers o
toWindowEventHandlers :: IsWindowEventHandlers o => o -> WindowEventHandlers
toWindowEventHandlers = WindowEventHandlers . coerce
instance IsWindowEventHandlers WindowEventHandlers
instance IsGObject WindowEventHandlers where
typeGType _ = gTypeWindowEventHandlers
{-# INLINE typeGType #-}
noWindowEventHandlers :: Maybe WindowEventHandlers
noWindowEventHandlers = Nothing
{-# INLINE noWindowEventHandlers #-}
gTypeWindowEventHandlers :: JSM GType
gTypeWindowEventHandlers = GType . Object <$> jsg "WindowEventHandlers"
newtype WindowOrWorkerGlobalScope = WindowOrWorkerGlobalScope { unWindowOrWorkerGlobalScope :: JSVal }
instance PToJSVal WindowOrWorkerGlobalScope where
pToJSVal = unWindowOrWorkerGlobalScope
{-# INLINE pToJSVal #-}
instance PFromJSVal WindowOrWorkerGlobalScope where
pFromJSVal = WindowOrWorkerGlobalScope
{-# INLINE pFromJSVal #-}
instance ToJSVal WindowOrWorkerGlobalScope where
toJSVal = return . unWindowOrWorkerGlobalScope
{-# INLINE toJSVal #-}
instance FromJSVal WindowOrWorkerGlobalScope where
fromJSVal v = fmap WindowOrWorkerGlobalScope <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WindowOrWorkerGlobalScope
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WindowOrWorkerGlobalScope where
makeObject = makeObject . unWindowOrWorkerGlobalScope
class (IsGObject o) => IsWindowOrWorkerGlobalScope o
toWindowOrWorkerGlobalScope :: IsWindowOrWorkerGlobalScope o => o -> WindowOrWorkerGlobalScope
toWindowOrWorkerGlobalScope = WindowOrWorkerGlobalScope . coerce
instance IsWindowOrWorkerGlobalScope WindowOrWorkerGlobalScope
instance IsGObject WindowOrWorkerGlobalScope where
typeGType _ = gTypeWindowOrWorkerGlobalScope
{-# INLINE typeGType #-}
noWindowOrWorkerGlobalScope :: Maybe WindowOrWorkerGlobalScope
noWindowOrWorkerGlobalScope = Nothing
{-# INLINE noWindowOrWorkerGlobalScope #-}
gTypeWindowOrWorkerGlobalScope :: JSM GType
gTypeWindowOrWorkerGlobalScope = GType . Object <$> jsg "WindowOrWorkerGlobalScope"
newtype Worker = Worker { unWorker :: JSVal }
instance PToJSVal Worker where
pToJSVal = unWorker
{-# INLINE pToJSVal #-}
instance PFromJSVal Worker where
pFromJSVal = Worker
{-# INLINE pFromJSVal #-}
instance ToJSVal Worker where
toJSVal = return . unWorker
{-# INLINE toJSVal #-}
instance FromJSVal Worker where
fromJSVal v = fmap Worker <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . Worker
{-# INLINE fromJSValUnchecked #-}
instance MakeObject Worker where
makeObject = makeObject . unWorker
instance IsEventTarget Worker
instance IsAbstractWorker Worker
instance IsGObject Worker where
typeGType _ = gTypeWorker
{-# INLINE typeGType #-}
noWorker :: Maybe Worker
noWorker = Nothing
{-# INLINE noWorker #-}
gTypeWorker :: JSM GType
gTypeWorker = GType . Object <$> jsg "Worker"
newtype WorkerGlobalScope = WorkerGlobalScope { unWorkerGlobalScope :: JSVal }
instance PToJSVal WorkerGlobalScope where
pToJSVal = unWorkerGlobalScope
{-# INLINE pToJSVal #-}
instance PFromJSVal WorkerGlobalScope where
pFromJSVal = WorkerGlobalScope
{-# INLINE pFromJSVal #-}
instance ToJSVal WorkerGlobalScope where
toJSVal = return . unWorkerGlobalScope
{-# INLINE toJSVal #-}
instance FromJSVal WorkerGlobalScope where
fromJSVal v = fmap WorkerGlobalScope <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WorkerGlobalScope
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WorkerGlobalScope where
makeObject = makeObject . unWorkerGlobalScope
class (IsEventTarget o, IsWindowOrWorkerGlobalScope o, IsGlobalPerformance o, IsGlobalCrypto o, IsGObject o) => IsWorkerGlobalScope o
toWorkerGlobalScope :: IsWorkerGlobalScope o => o -> WorkerGlobalScope
toWorkerGlobalScope = WorkerGlobalScope . coerce
instance IsWorkerGlobalScope WorkerGlobalScope
instance IsEventTarget WorkerGlobalScope
instance IsWindowOrWorkerGlobalScope WorkerGlobalScope
instance IsGlobalPerformance WorkerGlobalScope
instance IsGlobalCrypto WorkerGlobalScope
instance IsGObject WorkerGlobalScope where
typeGType _ = gTypeWorkerGlobalScope
{-# INLINE typeGType #-}
noWorkerGlobalScope :: Maybe WorkerGlobalScope
noWorkerGlobalScope = Nothing
{-# INLINE noWorkerGlobalScope #-}
gTypeWorkerGlobalScope :: JSM GType
gTypeWorkerGlobalScope = GType . Object <$> jsg "WorkerGlobalScope"
newtype WorkerLocation = WorkerLocation { unWorkerLocation :: JSVal }
instance PToJSVal WorkerLocation where
pToJSVal = unWorkerLocation
{-# INLINE pToJSVal #-}
instance PFromJSVal WorkerLocation where
pFromJSVal = WorkerLocation
{-# INLINE pFromJSVal #-}
instance ToJSVal WorkerLocation where
toJSVal = return . unWorkerLocation
{-# INLINE toJSVal #-}
instance FromJSVal WorkerLocation where
fromJSVal v = fmap WorkerLocation <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WorkerLocation
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WorkerLocation where
makeObject = makeObject . unWorkerLocation
instance IsGObject WorkerLocation where
typeGType _ = gTypeWorkerLocation
{-# INLINE typeGType #-}
noWorkerLocation :: Maybe WorkerLocation
noWorkerLocation = Nothing
{-# INLINE noWorkerLocation #-}
gTypeWorkerLocation :: JSM GType
gTypeWorkerLocation = GType . Object <$> jsg "WorkerLocation"
newtype WorkerNavigator = WorkerNavigator { unWorkerNavigator :: JSVal }
instance PToJSVal WorkerNavigator where
pToJSVal = unWorkerNavigator
{-# INLINE pToJSVal #-}
instance PFromJSVal WorkerNavigator where
pFromJSVal = WorkerNavigator
{-# INLINE pFromJSVal #-}
instance ToJSVal WorkerNavigator where
toJSVal = return . unWorkerNavigator
{-# INLINE toJSVal #-}
instance FromJSVal WorkerNavigator where
fromJSVal v = fmap WorkerNavigator <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WorkerNavigator
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WorkerNavigator where
makeObject = makeObject . unWorkerNavigator
instance IsNavigatorOnLine WorkerNavigator
instance IsNavigatorLanguage WorkerNavigator
instance IsNavigatorID WorkerNavigator
instance IsNavigatorConcurrentHardware WorkerNavigator
instance IsGObject WorkerNavigator where
typeGType _ = gTypeWorkerNavigator
{-# INLINE typeGType #-}
noWorkerNavigator :: Maybe WorkerNavigator
noWorkerNavigator = Nothing
{-# INLINE noWorkerNavigator #-}
gTypeWorkerNavigator :: JSM GType
gTypeWorkerNavigator = GType . Object <$> jsg "WorkerNavigator"
newtype WritableStream = WritableStream { unWritableStream :: JSVal }
instance PToJSVal WritableStream where
pToJSVal = unWritableStream
{-# INLINE pToJSVal #-}
instance PFromJSVal WritableStream where
pFromJSVal = WritableStream
{-# INLINE pFromJSVal #-}
instance ToJSVal WritableStream where
toJSVal = return . unWritableStream
{-# INLINE toJSVal #-}
instance FromJSVal WritableStream where
fromJSVal v = fmap WritableStream <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . WritableStream
{-# INLINE fromJSValUnchecked #-}
instance MakeObject WritableStream where
makeObject = makeObject . unWritableStream
instance IsGObject WritableStream where
typeGType _ = gTypeWritableStream
{-# INLINE typeGType #-}
noWritableStream :: Maybe WritableStream
noWritableStream = Nothing
{-# INLINE noWritableStream #-}
gTypeWritableStream :: JSM GType
gTypeWritableStream = GType . Object <$> jsg "WritableStream"
newtype XMLDocument = XMLDocument { unXMLDocument :: JSVal }
instance PToJSVal XMLDocument where
pToJSVal = unXMLDocument
{-# INLINE pToJSVal #-}
instance PFromJSVal XMLDocument where
pFromJSVal = XMLDocument
{-# INLINE pFromJSVal #-}
instance ToJSVal XMLDocument where
toJSVal = return . unXMLDocument
{-# INLINE toJSVal #-}
instance FromJSVal XMLDocument where
fromJSVal v = fmap XMLDocument <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XMLDocument
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XMLDocument where
makeObject = makeObject . unXMLDocument
instance IsDocument XMLDocument
instance IsNode XMLDocument
instance IsEventTarget XMLDocument
instance IsGlobalEventHandlers XMLDocument
instance IsDocumentOrShadowRoot XMLDocument
instance IsNonElementParentNode XMLDocument
instance IsParentNode XMLDocument
instance IsDocumentAndElementEventHandlers XMLDocument
instance IsGObject XMLDocument where
typeGType _ = gTypeXMLDocument
{-# INLINE typeGType #-}
noXMLDocument :: Maybe XMLDocument
noXMLDocument = Nothing
{-# INLINE noXMLDocument #-}
gTypeXMLDocument :: JSM GType
gTypeXMLDocument = GType . Object <$> jsg "XMLDocument"
newtype XMLHttpRequest = XMLHttpRequest { unXMLHttpRequest :: JSVal }
instance PToJSVal XMLHttpRequest where
pToJSVal = unXMLHttpRequest
{-# INLINE pToJSVal #-}
instance PFromJSVal XMLHttpRequest where
pFromJSVal = XMLHttpRequest
{-# INLINE pFromJSVal #-}
instance ToJSVal XMLHttpRequest where
toJSVal = return . unXMLHttpRequest
{-# INLINE toJSVal #-}
instance FromJSVal XMLHttpRequest where
fromJSVal v = fmap XMLHttpRequest <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XMLHttpRequest
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XMLHttpRequest where
makeObject = makeObject . unXMLHttpRequest
instance IsXMLHttpRequestEventTarget XMLHttpRequest
instance IsEventTarget XMLHttpRequest
instance IsGObject XMLHttpRequest where
typeGType _ = gTypeXMLHttpRequest
{-# INLINE typeGType #-}
noXMLHttpRequest :: Maybe XMLHttpRequest
noXMLHttpRequest = Nothing
{-# INLINE noXMLHttpRequest #-}
gTypeXMLHttpRequest :: JSM GType
gTypeXMLHttpRequest = GType . Object <$> jsg "XMLHttpRequest"
newtype XMLHttpRequestEventTarget = XMLHttpRequestEventTarget { unXMLHttpRequestEventTarget :: JSVal }
instance PToJSVal XMLHttpRequestEventTarget where
pToJSVal = unXMLHttpRequestEventTarget
{-# INLINE pToJSVal #-}
instance PFromJSVal XMLHttpRequestEventTarget where
pFromJSVal = XMLHttpRequestEventTarget
{-# INLINE pFromJSVal #-}
instance ToJSVal XMLHttpRequestEventTarget where
toJSVal = return . unXMLHttpRequestEventTarget
{-# INLINE toJSVal #-}
instance FromJSVal XMLHttpRequestEventTarget where
fromJSVal v = fmap XMLHttpRequestEventTarget <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XMLHttpRequestEventTarget
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XMLHttpRequestEventTarget where
makeObject = makeObject . unXMLHttpRequestEventTarget
class (IsEventTarget o, IsGObject o) => IsXMLHttpRequestEventTarget o
toXMLHttpRequestEventTarget :: IsXMLHttpRequestEventTarget o => o -> XMLHttpRequestEventTarget
toXMLHttpRequestEventTarget = XMLHttpRequestEventTarget . coerce
instance IsXMLHttpRequestEventTarget XMLHttpRequestEventTarget
instance IsEventTarget XMLHttpRequestEventTarget
instance IsGObject XMLHttpRequestEventTarget where
typeGType _ = gTypeXMLHttpRequestEventTarget
{-# INLINE typeGType #-}
noXMLHttpRequestEventTarget :: Maybe XMLHttpRequestEventTarget
noXMLHttpRequestEventTarget = Nothing
{-# INLINE noXMLHttpRequestEventTarget #-}
gTypeXMLHttpRequestEventTarget :: JSM GType
gTypeXMLHttpRequestEventTarget = GType . Object <$> jsg "XMLHttpRequestEventTarget"
newtype XMLHttpRequestProgressEvent = XMLHttpRequestProgressEvent { unXMLHttpRequestProgressEvent :: JSVal }
instance PToJSVal XMLHttpRequestProgressEvent where
pToJSVal = unXMLHttpRequestProgressEvent
{-# INLINE pToJSVal #-}
instance PFromJSVal XMLHttpRequestProgressEvent where
pFromJSVal = XMLHttpRequestProgressEvent
{-# INLINE pFromJSVal #-}
instance ToJSVal XMLHttpRequestProgressEvent where
toJSVal = return . unXMLHttpRequestProgressEvent
{-# INLINE toJSVal #-}
instance FromJSVal XMLHttpRequestProgressEvent where
fromJSVal v = fmap XMLHttpRequestProgressEvent <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XMLHttpRequestProgressEvent
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XMLHttpRequestProgressEvent where
makeObject = makeObject . unXMLHttpRequestProgressEvent
instance IsProgressEvent XMLHttpRequestProgressEvent
instance IsEvent XMLHttpRequestProgressEvent
instance IsGObject XMLHttpRequestProgressEvent where
typeGType _ = gTypeXMLHttpRequestProgressEvent
{-# INLINE typeGType #-}
noXMLHttpRequestProgressEvent :: Maybe XMLHttpRequestProgressEvent
noXMLHttpRequestProgressEvent = Nothing
{-# INLINE noXMLHttpRequestProgressEvent #-}
gTypeXMLHttpRequestProgressEvent :: JSM GType
gTypeXMLHttpRequestProgressEvent = GType . Object <$> jsg "XMLHttpRequestProgressEvent"
newtype XMLHttpRequestUpload = XMLHttpRequestUpload { unXMLHttpRequestUpload :: JSVal }
instance PToJSVal XMLHttpRequestUpload where
pToJSVal = unXMLHttpRequestUpload
{-# INLINE pToJSVal #-}
instance PFromJSVal XMLHttpRequestUpload where
pFromJSVal = XMLHttpRequestUpload
{-# INLINE pFromJSVal #-}
instance ToJSVal XMLHttpRequestUpload where
toJSVal = return . unXMLHttpRequestUpload
{-# INLINE toJSVal #-}
instance FromJSVal XMLHttpRequestUpload where
fromJSVal v = fmap XMLHttpRequestUpload <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XMLHttpRequestUpload
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XMLHttpRequestUpload where
makeObject = makeObject . unXMLHttpRequestUpload
instance IsXMLHttpRequestEventTarget XMLHttpRequestUpload
instance IsEventTarget XMLHttpRequestUpload
instance IsGObject XMLHttpRequestUpload where
typeGType _ = gTypeXMLHttpRequestUpload
{-# INLINE typeGType #-}
noXMLHttpRequestUpload :: Maybe XMLHttpRequestUpload
noXMLHttpRequestUpload = Nothing
{-# INLINE noXMLHttpRequestUpload #-}
gTypeXMLHttpRequestUpload :: JSM GType
gTypeXMLHttpRequestUpload = GType . Object <$> jsg "XMLHttpRequestUpload"
newtype XMLSerializer = XMLSerializer { unXMLSerializer :: JSVal }
instance PToJSVal XMLSerializer where
pToJSVal = unXMLSerializer
{-# INLINE pToJSVal #-}
instance PFromJSVal XMLSerializer where
pFromJSVal = XMLSerializer
{-# INLINE pFromJSVal #-}
instance ToJSVal XMLSerializer where
toJSVal = return . unXMLSerializer
{-# INLINE toJSVal #-}
instance FromJSVal XMLSerializer where
fromJSVal v = fmap XMLSerializer <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XMLSerializer
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XMLSerializer where
makeObject = makeObject . unXMLSerializer
instance IsGObject XMLSerializer where
typeGType _ = gTypeXMLSerializer
{-# INLINE typeGType #-}
noXMLSerializer :: Maybe XMLSerializer
noXMLSerializer = Nothing
{-# INLINE noXMLSerializer #-}
gTypeXMLSerializer :: JSM GType
gTypeXMLSerializer = GType . Object <$> jsg "XMLSerializer"
newtype XPathEvaluator = XPathEvaluator { unXPathEvaluator :: JSVal }
instance PToJSVal XPathEvaluator where
pToJSVal = unXPathEvaluator
{-# INLINE pToJSVal #-}
instance PFromJSVal XPathEvaluator where
pFromJSVal = XPathEvaluator
{-# INLINE pFromJSVal #-}
instance ToJSVal XPathEvaluator where
toJSVal = return . unXPathEvaluator
{-# INLINE toJSVal #-}
instance FromJSVal XPathEvaluator where
fromJSVal v = fmap XPathEvaluator <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XPathEvaluator
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XPathEvaluator where
makeObject = makeObject . unXPathEvaluator
instance IsGObject XPathEvaluator where
typeGType _ = gTypeXPathEvaluator
{-# INLINE typeGType #-}
noXPathEvaluator :: Maybe XPathEvaluator
noXPathEvaluator = Nothing
{-# INLINE noXPathEvaluator #-}
gTypeXPathEvaluator :: JSM GType
gTypeXPathEvaluator = GType . Object <$> jsg "XPathEvaluator"
newtype XPathException = XPathException { unXPathException :: JSVal }
instance PToJSVal XPathException where
pToJSVal = unXPathException
{-# INLINE pToJSVal #-}
instance PFromJSVal XPathException where
pFromJSVal = XPathException
{-# INLINE pFromJSVal #-}
instance ToJSVal XPathException where
toJSVal = return . unXPathException
{-# INLINE toJSVal #-}
instance FromJSVal XPathException where
fromJSVal v = fmap XPathException <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XPathException
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XPathException where
makeObject = makeObject . unXPathException
instance IsGObject XPathException where
typeGType _ = gTypeXPathException
{-# INLINE typeGType #-}
noXPathException :: Maybe XPathException
noXPathException = Nothing
{-# INLINE noXPathException #-}
gTypeXPathException :: JSM GType
gTypeXPathException = GType . Object <$> jsg "XPathException"
newtype XPathExpression = XPathExpression { unXPathExpression :: JSVal }
instance PToJSVal XPathExpression where
pToJSVal = unXPathExpression
{-# INLINE pToJSVal #-}
instance PFromJSVal XPathExpression where
pFromJSVal = XPathExpression
{-# INLINE pFromJSVal #-}
instance ToJSVal XPathExpression where
toJSVal = return . unXPathExpression
{-# INLINE toJSVal #-}
instance FromJSVal XPathExpression where
fromJSVal v = fmap XPathExpression <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XPathExpression
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XPathExpression where
makeObject = makeObject . unXPathExpression
instance IsGObject XPathExpression where
typeGType _ = gTypeXPathExpression
{-# INLINE typeGType #-}
noXPathExpression :: Maybe XPathExpression
noXPathExpression = Nothing
{-# INLINE noXPathExpression #-}
gTypeXPathExpression :: JSM GType
gTypeXPathExpression = GType . Object <$> jsg "XPathExpression"
newtype XPathNSResolver = XPathNSResolver { unXPathNSResolver :: JSVal }
instance PToJSVal XPathNSResolver where
pToJSVal = unXPathNSResolver
{-# INLINE pToJSVal #-}
instance PFromJSVal XPathNSResolver where
pFromJSVal = XPathNSResolver
{-# INLINE pFromJSVal #-}
instance ToJSVal XPathNSResolver where
toJSVal = return . unXPathNSResolver
{-# INLINE toJSVal #-}
instance FromJSVal XPathNSResolver where
fromJSVal v = fmap XPathNSResolver <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XPathNSResolver
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XPathNSResolver where
makeObject = makeObject . unXPathNSResolver
instance IsGObject XPathNSResolver where
typeGType _ = gTypeXPathNSResolver
{-# INLINE typeGType #-}
noXPathNSResolver :: Maybe XPathNSResolver
noXPathNSResolver = Nothing
{-# INLINE noXPathNSResolver #-}
gTypeXPathNSResolver :: JSM GType
gTypeXPathNSResolver = GType . Object <$> jsg "XPathNSResolver"
newtype XPathResult = XPathResult { unXPathResult :: JSVal }
instance PToJSVal XPathResult where
pToJSVal = unXPathResult
{-# INLINE pToJSVal #-}
instance PFromJSVal XPathResult where
pFromJSVal = XPathResult
{-# INLINE pFromJSVal #-}
instance ToJSVal XPathResult where
toJSVal = return . unXPathResult
{-# INLINE toJSVal #-}
instance FromJSVal XPathResult where
fromJSVal v = fmap XPathResult <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XPathResult
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XPathResult where
makeObject = makeObject . unXPathResult
instance IsGObject XPathResult where
typeGType _ = gTypeXPathResult
{-# INLINE typeGType #-}
noXPathResult :: Maybe XPathResult
noXPathResult = Nothing
{-# INLINE noXPathResult #-}
gTypeXPathResult :: JSM GType
gTypeXPathResult = GType . Object <$> jsg "XPathResult"
newtype XSLTProcessor = XSLTProcessor { unXSLTProcessor :: JSVal }
instance PToJSVal XSLTProcessor where
pToJSVal = unXSLTProcessor
{-# INLINE pToJSVal #-}
instance PFromJSVal XSLTProcessor where
pFromJSVal = XSLTProcessor
{-# INLINE pFromJSVal #-}
instance ToJSVal XSLTProcessor where
toJSVal = return . unXSLTProcessor
{-# INLINE toJSVal #-}
instance FromJSVal XSLTProcessor where
fromJSVal v = fmap XSLTProcessor <$> maybeNullOrUndefined v
{-# INLINE fromJSVal #-}
fromJSValUnchecked = return . XSLTProcessor
{-# INLINE fromJSValUnchecked #-}
instance MakeObject XSLTProcessor where
makeObject = makeObject . unXSLTProcessor
instance IsGObject XSLTProcessor where
typeGType _ = gTypeXSLTProcessor
{-# INLINE typeGType #-}
noXSLTProcessor :: Maybe XSLTProcessor
noXSLTProcessor = Nothing
{-# INLINE noXSLTProcessor #-}
gTypeXSLTProcessor :: JSM GType
gTypeXSLTProcessor = GType . Object <$> jsg "XSLTProcessor"