{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Types (
  -- * JavaScript Context and Monad
    JSContextRef(..), JSM, askJSM, runJSM, MonadJSM(..), liftJSM

  -- * DOM Context and Monad
  , DOMContext(..), DOM, askDOM, runDOM, MonadDOM(..), liftDOM

  -- * JavaScript Value
  , JSVal(..), ToJSVal(..), FromJSVal(..), PToJSVal(..), PFromJSVal(..)
  , integralToDoubleToJSVal, integralFromDoubleFromJSVal, integralFromDoubleFromJSValUnchecked

  -- * JavaScript String
  , JSString(..), ToJSString(..), FromJSString(..)
  , toMaybeJSString, fromMaybeJSString
  , noJSString

  -- * JavaScript Array
  , fromJSArray, fromJSArrayUnchecked

  -- * JavaScript Object
  , Object(..)

  -- * Nullable
  , Nullable(..), nullableToMaybe, maybeToNullable

  -- * DOM String
  , DOMString(..), ToDOMString(..), FromDOMString(..), IsDOMString, noDOMString
  , USVString(..), IsUSVString, noUSVString
  , ByteString(..), IsByteString, noByteString
  , CSSOMString(..), IsCSSOMString, noCSSOMString

  -- * Object
  , maybeNullOrUndefined, maybeNullOrUndefined', GType(..)
  , GObject(..), noGObject, IsGObject, toGObject, gTypeGObject, isA, objectToString
  , castTo, unsafeCastTo, uncheckedCastTo
  , strictEqual

  -- * TypedArray
  , RawTypedArray(RawTypedArray), unRawTypedArray, IsRawTypedArray, toRawTypedArray, noRawTypedArray

  , Function(Function), unFunction, IsFunction, toFunction, noFunction

  -- * Promise
  , PromiseRejected(..), noPromiseRejected, readPromise

  -- * Callbacks
  , 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

  -- * Custom Types
  , DOMHighResTimeStamp, noDOMHighResTimeStamp
  , PerformanceEntryList, noPerformanceEntryList

  -- * Record Type
  , Record(Record), unRecord

  -- * Dictionaries
  , Dictionary(Dictionary), unDictionary, IsDictionary, toDictionary, noDictionary

  -- * Mutation Callback
  , MutationCallback(MutationCallback), unMutationCallback, IsMutationCallback, toMutationCallback, noMutationCallback

  -- * Date
  , Date(Date), unDate, IsDate, toDate, gTypeDate, noDate

  -- * Arrays
  , 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

  -- * Geolocation
  , SerializedScriptValue(SerializedScriptValue), unSerializedScriptValue, IsSerializedScriptValue, toSerializedScriptValue, noSerializedScriptValue

  -- * Crypto
  , Algorithm(Algorithm), unAlgorithm, IsAlgorithm, toAlgorithm, noAlgorithm
  , CryptoOperationData(CryptoOperationData), unCryptoOperationData, IsCryptoOperationData, toCryptoOperationData, noCryptoOperationData

  -- * WebGL typedefs
  , 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

  -- * Used for better error messages
  , HasCallStack

  , GlobalThis(GlobalThis), unGlobalThis, noGlobalThis

  -- * Interface types from IDL files

-- AUTO GENERATION STARTS HERE
  , 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
-- AUTO GENERATION ENDS HERE
  ) 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

-- | This is the same as 'JSM' except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
type DOM = JSM
-- | This is the same as 'JSContextRef' except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
type DOMContext = JSContextRef
-- | This is the same as 'MonadJSM' except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
type MonadDOM = MonadJSM

-- | This is the same as 'liftJSM' except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
liftDOM :: MonadDOM m => DOM a -> m a
liftDOM :: forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM = JSM a -> m a
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftJSM

-- | This is the same as 'askJSM' except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
askDOM :: MonadDOM m => m DOMContext
askDOM :: forall (m :: * -> *). MonadDOM m => m DOMContext
askDOM = m DOMContext
forall (m :: * -> *). MonadDOM m => m DOMContext
askJSM

-- | This is the same as 'runJSM' except when using ghcjs-dom-webkit with GHC (instead of ghcjs-dom-jsaddle)
runDOM :: MonadIO m => DOM a -> DOMContext -> m a
runDOM :: forall (m :: * -> *) a. MonadIO m => DOM a -> DOMContext -> m a
runDOM = JSM a -> DOMContext -> m a
forall (m :: * -> *) a. MonadIO m => DOM a -> DOMContext -> m a
runJSM

newtype GType = GType Object

typeInstanceIsA :: ToJSVal value => value -> GType -> JSM Bool
typeInstanceIsA :: forall value. ToJSVal value => value -> GType -> JSM Bool
typeInstanceIsA value
o (GType Object
t) = value
o value -> Object -> JSM Bool
forall value constructor.
(ToJSVal value, MakeObject constructor) =>
value -> constructor -> JSM Bool
`instanceOf` Object
t

-- | Safe but slow way to cast
--
-- > castTo Element x >>= \case
-- >     Nothing      -> error "Was not an element"
-- >     Just element -> ...
castTo :: forall obj obj' m. (Coercible obj JSVal, IsGObject obj', MonadJSM m) => (JSVal -> obj') -> obj -> m (Maybe obj')
castTo :: forall obj obj' (m :: * -> *).
(Coercible obj JSVal, IsGObject obj', MonadJSM m) =>
(JSVal -> obj') -> obj -> m (Maybe obj')
castTo JSVal -> obj'
constructor obj
obj = JSM (Maybe obj') -> m (Maybe obj')
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftJSM (JSM (Maybe obj') -> m (Maybe obj'))
-> JSM (Maybe obj') -> m (Maybe obj')
forall a b. (a -> b) -> a -> b
$ do
  GType Object
gtype <- obj' -> JSM GType
forall o. IsGObject o => o -> JSM GType
typeGType (obj'
forall a. HasCallStack => a
undefined :: obj')
  let jsval :: JSVal
jsval = obj -> JSVal
forall a b. Coercible a b => a -> b
coerce obj
obj
  JSVal
jsval JSVal -> Object -> JSM Bool
forall value constructor.
(ToJSVal value, MakeObject constructor) =>
value -> constructor -> JSM Bool
`instanceOf` Object
gtype JSM Bool -> (Bool -> JSM (Maybe obj')) -> JSM (Maybe obj')
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Bool
True  -> Maybe obj' -> JSM (Maybe obj')
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe obj' -> JSM (Maybe obj'))
-> (obj' -> Maybe obj') -> obj' -> JSM (Maybe obj')
forall b c a. (b -> c) -> (a -> b) -> a -> c
. obj' -> Maybe obj'
forall a. a -> Maybe a
Just (obj' -> JSM (Maybe obj')) -> obj' -> JSM (Maybe obj')
forall a b. (a -> b) -> a -> b
$ JSVal -> obj'
constructor JSVal
jsval
    Bool
False -> Maybe obj' -> JSM (Maybe obj')
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe obj'
forall a. Maybe a
Nothing

-- | Unsafe way to cast.  Slow but if it fails an error message will
--   result and the message should be clear (uses HasCallStack).
--
-- > element <- unsafeCastTo Element x
unsafeCastTo :: forall obj obj' m. (HasCallStack, Coercible obj JSVal, IsGObject obj', MonadJSM m) => (JSVal -> obj') -> obj -> m obj'
unsafeCastTo :: forall obj obj' (m :: * -> *).
(HasCallStack, Coercible obj JSVal, IsGObject obj', MonadJSM m) =>
(JSVal -> obj') -> obj -> m obj'
unsafeCastTo JSVal -> obj'
constructor obj
obj = JSM obj' -> m obj'
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftJSM (JSM obj' -> m obj') -> JSM obj' -> m obj'
forall a b. (a -> b) -> a -> b
$ do
  GType Object
gtype <- obj' -> JSM GType
forall o. IsGObject o => o -> JSM GType
typeGType (obj'
forall a. HasCallStack => a
undefined :: obj')
  let jsval :: JSVal
jsval = obj -> JSVal
forall a b. Coercible a b => a -> b
coerce obj
obj
  JSVal
jsval JSVal -> Object -> JSM Bool
forall value constructor.
(ToJSVal value, MakeObject constructor) =>
value -> constructor -> JSM Bool
`instanceOf` Object
gtype JSM Bool -> (Bool -> JSM obj') -> JSM obj'
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Bool
True  -> obj' -> JSM obj'
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (obj' -> JSM obj') -> obj' -> JSM obj'
forall a b. (a -> b) -> a -> b
$ JSVal -> obj'
constructor JSVal
jsval
    Bool
False -> do
      Text
destType <- JSM JSVal -> JSM Text
forall value. ToJSVal value => value -> JSM Text
valToText (Object
gtype Object -> Getting (JSM JSVal) Object (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter Object (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"name")
      String -> JSM obj'
forall a. HasCallStack => String -> a
error (String -> JSM obj') -> String -> JSM obj'
forall a b. (a -> b) -> a -> b
$ String
"unsafeCastTo :: invalid conversion to "
        String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
destType String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" requested."

-- | Unsafe way to cast.  Fast but if it fails you program
--   will probably crash later on in some unpredictable way.
--
-- > element <- uncheckedCastTo Element x
uncheckedCastTo :: (Coercible obj JSVal, IsGObject obj') => (JSVal -> obj') -> obj -> obj'
uncheckedCastTo :: forall obj obj'.
(Coercible obj JSVal, IsGObject obj') =>
(JSVal -> obj') -> obj -> obj'
uncheckedCastTo JSVal -> obj'
constructor = JSVal -> obj'
constructor (JSVal -> obj') -> (obj -> JSVal) -> obj -> obj'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. obj -> JSVal
forall a b. Coercible a b => a -> b
coerce

-- | Determine if this is an instance of a particular type
--
isA :: IsGObject o => o -> GType -> JSM Bool
isA :: forall o. IsGObject o => o -> GType -> JSM Bool
isA o
obj = JSVal -> GType -> JSM Bool
forall value. ToJSVal value => value -> GType -> JSM Bool
typeInstanceIsA (GObject -> JSVal
unGObject (GObject -> JSVal) -> GObject -> JSVal
forall a b. (a -> b) -> a -> b
$ o -> GObject
forall o. IsGObject o => o -> GObject
toGObject o
obj)

newtype GObject = GObject { GObject -> JSVal
unGObject :: JSVal }
noGObject :: Maybe GObject
noGObject :: Maybe GObject
noGObject = Maybe GObject
forall a. Maybe a
Nothing
{-# INLINE noGObject #-}

class (ToJSVal o, FromJSVal o, Coercible o JSVal) => IsGObject o where
  -- | Given object get the GType of the type.  The actual argument
  --   passed in is ignored.
  typeGType :: o -> JSM GType

-- | Safe upcast.
toGObject :: IsGObject o => o -> GObject
toGObject :: forall o. IsGObject o => o -> GObject
toGObject = JSVal -> GObject
GObject (JSVal -> GObject) -> (o -> JSVal) -> o -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

fromJSArray :: FromJSVal o => JSVal -> JSM [Maybe o]
fromJSArray :: forall o. FromJSVal o => JSVal -> JSM [Maybe o]
fromJSArray JSVal
a = do
    Double
l <- JSVal
a JSVal -> Getting (JSM JSVal) JSVal (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter JSVal (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"length" JSM JSVal -> (JSVal -> JSM Double) -> JSM Double
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> JSM Double
forall value. ToJSVal value => value -> JSM Double
valToNumber
    (Int -> JSM (Maybe o)) -> [Int] -> JSM [Maybe o]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\Int
i -> JSVal
a JSVal -> Int -> JSM JSVal
forall this. MakeObject this => this -> Int -> JSM JSVal
!! Int
i JSM JSVal -> (JSVal -> JSM (Maybe o)) -> JSM (Maybe o)
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> JSM (Maybe o)
forall a. FromJSVal a => JSVal -> JSM (Maybe a)
fromJSVal) [Int
0..Double -> Int
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
round Double
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]

fromJSArrayUnchecked :: FromJSVal o => JSVal -> JSM [o]
fromJSArrayUnchecked :: forall o. FromJSVal o => JSVal -> JSM [o]
fromJSArrayUnchecked = JSVal -> JSM [o]
forall o. FromJSVal o => JSVal -> JSM [o]
fromJSValUncheckedListOf

-- newtype Nullable a = Nullable JSVal

nullableToMaybe :: FromJSVal a => JSVal -> JSM (Maybe a)
nullableToMaybe :: forall a. FromJSVal a => JSVal -> JSM (Maybe a)
nullableToMaybe = JSVal -> JSM (Maybe a)
forall a. FromJSVal a => JSVal -> JSM (Maybe a)
fromJSVal
{-# INLINE nullableToMaybe #-}
--
maybeToNullable :: ToJSVal a => Maybe a -> JSM JSVal
maybeToNullable :: forall a. ToJSVal a => Maybe a -> JSM JSVal
maybeToNullable Maybe a
Nothing = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return JSVal
valNull
maybeToNullable (Just a
a) = a -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal a
a
{-# INLINE maybeToNullable #-}

instance PToJSVal GObject where
  pToJSVal :: GObject -> JSVal
pToJSVal = GObject -> JSVal
unGObject
  {-# INLINE pToJSVal #-}

instance PFromJSVal GObject where
  pFromJSVal :: JSVal -> GObject
pFromJSVal = JSVal -> GObject
GObject
  {-# INLINE pFromJSVal #-}

instance ToJSVal GObject where
  toJSVal :: GObject -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (GObject -> JSVal) -> GObject -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> JSVal
unGObject
  {-# INLINE toJSVal #-}

instance FromJSVal GObject where
  fromJSVal :: JSVal -> JSM (Maybe GObject)
fromJSVal JSVal
val = (JSVal -> GObject) -> Maybe JSVal -> Maybe GObject
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> GObject
GObject (Maybe JSVal -> Maybe GObject)
-> JSM (Maybe JSVal) -> JSM (Maybe GObject)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
val
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM GObject
fromJSValUnchecked = GObject -> JSM GObject
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (GObject -> JSM GObject)
-> (JSVal -> GObject) -> JSVal -> JSM GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> GObject
GObject
  {-# INLINE fromJSValUnchecked #-}

--instance IsGObject o => PToJSVal o where
--  pToJSVal = unGObject . toGObject
--  {-# INLINE pToJSVal #-}
--
--instance IsGObject o => PFromJSVal o where
--  pFromJSVal = unsafeCastGObject . GObject . castRef
--  {-# INLINE pFromJSVal #-}
--
--instance IsGObject o => ToJSVal o where
--  toJSVal = return . unGObject . toGObject
--  {-# INLINE toJSVal #-}
--
--instance IsGObject o => FromJSVal o where
--  fromJSVal = return . fmap (unsafeCastGObject . GObject . castRef) . maybeJSNullOrUndefined
--  {-# INLINE fromJSVal #-}

instance IsGObject GObject where
  typeGType :: GObject -> JSM GType
typeGType GObject
_ = JSM GType
gTypeGObject
  {-# INLINE typeGType #-}

#ifdef ghcjs_HOST_OS
foreign import javascript unsafe "Object" gTypeGObject :: IO GType
#else
gTypeGObject :: JSM GType
gTypeGObject :: JSM GType
gTypeGObject = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Object"
#endif

objectToString :: (IsGObject self, FromJSString result) => self -> JSM result
objectToString :: forall self result.
(IsGObject self, FromJSString result) =>
self -> JSM result
objectToString self
self = JSVal -> JSM result
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked (GObject -> JSVal
unGObject (GObject -> JSVal) -> GObject -> JSVal
forall a b. (a -> b) -> a -> b
$ self -> GObject
forall o. IsGObject o => o -> GObject
toGObject self
self)

-- | Fastest string type to use when you just
--   want to take a string from the DOM then
--   give it back as is.
type DOMString = JSString
noDOMString :: Maybe DOMString
noDOMString :: Maybe DOMString
noDOMString = Maybe DOMString
forall a. Maybe a
Nothing
{-# INLINE noDOMString #-}
type CSSOMString = JSString
noCSSOMString :: Maybe CSSOMString
noCSSOMString :: Maybe DOMString
noCSSOMString = Maybe DOMString
forall a. Maybe a
Nothing
{-# INLINE noCSSOMString #-}
type USVString = JSString
noUSVString :: Maybe USVString
noUSVString :: Maybe DOMString
noUSVString = Maybe DOMString
forall a. Maybe a
Nothing
{-# INLINE noUSVString #-}
type ByteString = JSString
noByteString :: Maybe ByteString
noByteString :: Maybe DOMString
noByteString = Maybe DOMString
forall a. Maybe a
Nothing
{-# INLINE noByteString #-}

fromJSStringArray :: FromJSString s => JSVal -> JSM [s]
fromJSStringArray :: forall s. FromJSString s => JSVal -> JSM [s]
fromJSStringArray JSVal
a = do
    Double
l <- JSVal
a JSVal -> Getting (JSM JSVal) JSVal (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter JSVal (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"length" JSM JSVal -> (JSVal -> JSM Double) -> JSM Double
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> JSM Double
forall value. ToJSVal value => value -> JSM Double
valToNumber
    (Int -> JSM s) -> [Int] -> JSM [s]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\Int
i -> DOMString -> s
forall a. FromJSString a => DOMString -> a
fromJSString (DOMString -> s) -> JSM DOMString -> JSM s
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (JSVal
a JSVal -> Int -> JSM JSVal
forall this. MakeObject this => this -> Int -> JSM JSVal
!! Int
i JSM JSVal -> (JSVal -> JSM DOMString) -> JSM DOMString
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> JSM DOMString
forall value. ToJSVal value => value -> JSM DOMString
valToStr)) [Int
0..Double -> Int
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
round Double
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]

toMaybeJSString :: ToJSString a => Maybe a -> JSM JSVal
toMaybeJSString :: forall a. ToJSString a => Maybe a -> JSM JSVal
toMaybeJSString Maybe a
Nothing = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return JSVal
valNull
toMaybeJSString (Just a
a) = DOMString -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal (a -> DOMString
forall a. ToJSString a => a -> DOMString
toJSString a
a)
{-# INLINE toMaybeJSString #-}

fromMaybeJSString :: FromJSString a => JSVal -> JSM (Maybe a)
fromMaybeJSString :: forall a. FromJSString a => JSVal -> JSM (Maybe a)
fromMaybeJSString = (JSVal -> JSM a) -> JSVal -> JSM (Maybe a)
forall value a.
ToJSVal value =>
(JSVal -> JSM a) -> value -> JSM (Maybe a)
maybeNullOrUndefined' ((DOMString -> a) -> JSM DOMString -> JSM a
forall a b. (a -> b) -> JSM a -> JSM b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DOMString -> a
forall a. FromJSString a => DOMString -> a
fromJSString (JSM DOMString -> JSM a)
-> (JSVal -> JSM DOMString) -> JSVal -> JSM a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> JSM DOMString
forall value. ToJSVal value => value -> JSM DOMString
valToStr)
{-# INLINE fromMaybeJSString #-}

integralToDoubleToJSVal :: Integral a => a -> JSM JSVal
integralToDoubleToJSVal :: forall a. Integral a => a -> JSM JSVal
integralToDoubleToJSVal a
a = Double -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal (a -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a :: Double)

integralFromDoubleFromJSVal :: Integral a => JSVal -> JSM (Maybe a)
integralFromDoubleFromJSVal :: forall a. Integral a => JSVal -> JSM (Maybe a)
integralFromDoubleFromJSVal = (Maybe Double -> Maybe a) -> JSM (Maybe Double) -> JSM (Maybe a)
forall a b. (a -> b) -> JSM a -> JSM b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Double -> a) -> Maybe Double -> Maybe a
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Double -> a
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
round) (JSM (Maybe Double) -> JSM (Maybe a))
-> (JSVal -> JSM (Maybe Double)) -> JSVal -> JSM (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (JSVal -> JSM (Maybe Double)
forall a. FromJSVal a => JSVal -> JSM (Maybe a)
fromJSVal :: JSVal -> JSM (Maybe Double))

integralFromDoubleFromJSValUnchecked :: Integral a => JSVal -> JSM a
integralFromDoubleFromJSValUnchecked :: forall a. Integral a => JSVal -> JSM a
integralFromDoubleFromJSValUnchecked = (Double -> a) -> JSM Double -> JSM a
forall a b. (a -> b) -> JSM a -> JSM b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Double -> a
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
round (JSM Double -> JSM a) -> (JSVal -> JSM Double) -> JSVal -> JSM a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (JSVal -> JSM Double
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked :: JSVal -> JSM Double)

noJSString :: Maybe JSString
noJSString :: Maybe DOMString
noJSString = Maybe DOMString
forall a. Maybe a
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 { RawTypedArray -> JSVal
unRawTypedArray :: JSVal }
noRawTypedArray :: Maybe RawTypedArray
noRawTypedArray :: Maybe RawTypedArray
noRawTypedArray = Maybe RawTypedArray
forall a. Maybe a
Nothing
{-# INLINE noRawTypedArray #-}

instance PToJSVal RawTypedArray where
  pToJSVal :: RawTypedArray -> JSVal
pToJSVal = RawTypedArray -> JSVal
unRawTypedArray
  {-# INLINE pToJSVal #-}

instance PFromJSVal RawTypedArray where
  pFromJSVal :: JSVal -> RawTypedArray
pFromJSVal = JSVal -> RawTypedArray
RawTypedArray
  {-# INLINE pFromJSVal #-}

instance ToJSVal RawTypedArray where
  toJSVal :: RawTypedArray -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RawTypedArray -> JSVal) -> RawTypedArray -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RawTypedArray -> JSVal
unRawTypedArray
  {-# INLINE toJSVal #-}

instance FromJSVal RawTypedArray where
  fromJSVal :: JSVal -> JSM (Maybe RawTypedArray)
fromJSVal JSVal
v = (JSVal -> RawTypedArray) -> Maybe JSVal -> Maybe RawTypedArray
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RawTypedArray
RawTypedArray (Maybe JSVal -> Maybe RawTypedArray)
-> JSM (Maybe JSVal) -> JSM (Maybe RawTypedArray)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RawTypedArray
fromJSValUnchecked = RawTypedArray -> JSM RawTypedArray
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RawTypedArray -> JSM RawTypedArray)
-> (JSVal -> RawTypedArray) -> JSVal -> JSM RawTypedArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RawTypedArray
RawTypedArray
  {-# INLINE fromJSValUnchecked #-}

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRawTypedArray o

toRawTypedArray :: IsRawTypedArray o => o -> RawTypedArray
toRawTypedArray :: forall o. IsRawTypedArray o => o -> RawTypedArray
toRawTypedArray = JSVal -> RawTypedArray
RawTypedArray (JSVal -> RawTypedArray) -> (o -> JSVal) -> o -> RawTypedArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

newtype Function = Function { Function -> JSVal
unFunction :: JSVal }
noFunction :: Maybe Function
noFunction :: Maybe Function
noFunction = Maybe Function
forall a. Maybe a
Nothing
{-# INLINE noFunction #-}

instance PToJSVal Function where
  pToJSVal :: Function -> JSVal
pToJSVal = Function -> JSVal
unFunction
  {-# INLINE pToJSVal #-}

instance PFromJSVal Function where
  pFromJSVal :: JSVal -> Function
pFromJSVal = JSVal -> Function
Function
  {-# INLINE pFromJSVal #-}

instance ToJSVal Function where
  toJSVal :: Function -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Function -> JSVal) -> Function -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Function -> JSVal
unFunction
  {-# INLINE toJSVal #-}

instance FromJSVal Function where
  fromJSVal :: JSVal -> JSM (Maybe Function)
fromJSVal JSVal
v = (JSVal -> Function) -> Maybe JSVal -> Maybe Function
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Function
Function (Maybe JSVal -> Maybe Function)
-> JSM (Maybe JSVal) -> JSM (Maybe Function)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Function
fromJSValUnchecked = Function -> JSM Function
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Function -> JSM Function)
-> (JSVal -> Function) -> JSVal -> JSM Function
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Function
Function
  {-# INLINE fromJSValUnchecked #-}

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsFunction o

toFunction :: IsFunction o => o -> Function
toFunction :: forall o. IsFunction o => o -> Function
toFunction = JSVal -> Function
Function (JSVal -> Function) -> (o -> JSVal) -> o -> Function
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsFunction Function

-- Promise
newtype PromiseRejected = PromiseRejected { PromiseRejected -> String
rejectionReason :: String } deriving (Typeable)
noPromiseRejected :: Maybe PromiseRejected
noPromiseRejected :: Maybe PromiseRejected
noPromiseRejected = Maybe PromiseRejected
forall a. Maybe a
Nothing
{-# INLINE noPromiseRejected #-}

instance Show PromiseRejected where
    show :: PromiseRejected -> String
show (PromiseRejected String
reason) = String
"A promise was rejected: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
reason
instance Exception PromiseRejected

readPromise :: JSVal -> JSM JSVal
readPromise :: JSVal -> JSM JSVal
readPromise JSVal
promise = do
    MVar (Either JSVal JSVal)
resultMVar <- IO (MVar (Either JSVal JSVal)) -> JSM (MVar (Either JSVal JSVal))
forall a. IO a -> JSM a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO (MVar (Either JSVal JSVal))
forall a. IO (MVar a)
newEmptyMVar
    Function
success <- JSCallAsFunction -> JSM Function
function (\JSVal
_ JSVal
_ [JSVal
result] -> IO () -> JSM ()
forall a. IO a -> JSM a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> JSM ())
-> (Either JSVal JSVal -> IO ()) -> Either JSVal JSVal -> JSM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MVar (Either JSVal JSVal) -> Either JSVal JSVal -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar (Either JSVal JSVal)
resultMVar (Either JSVal JSVal -> JSM ()) -> Either JSVal JSVal -> JSM ()
forall a b. (a -> b) -> a -> b
$ JSVal -> Either JSVal JSVal
forall a b. b -> Either a b
Right JSVal
result)
    Function
error <- JSCallAsFunction -> JSM Function
function (\JSVal
_ JSVal
_ [JSVal
reason] -> IO () -> JSM ()
forall a. IO a -> JSM a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> JSM ())
-> (Either JSVal JSVal -> IO ()) -> Either JSVal JSVal -> JSM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MVar (Either JSVal JSVal) -> Either JSVal JSVal -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar (Either JSVal JSVal)
resultMVar (Either JSVal JSVal -> JSM ()) -> Either JSVal JSVal -> JSM ()
forall a b. (a -> b) -> a -> b
$ JSVal -> Either JSVal JSVal
forall a b. a -> Either a b
Left JSVal
reason)
    JSVal
promise JSVal -> Getting (JSM JSVal) JSVal (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> Function -> Function -> JSF
forall name a0 a1.
(ToJSString name, ToJSVal a0, ToJSVal a1) =>
name -> a0 -> a1 -> JSF
js2 String
"then" Function
success Function
error
    Either JSVal JSVal
result <- IO (Either JSVal JSVal) -> JSM (Either JSVal JSVal)
forall a. IO a -> JSM a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either JSVal JSVal) -> JSM (Either JSVal JSVal))
-> IO (Either JSVal JSVal) -> JSM (Either JSVal JSVal)
forall a b. (a -> b) -> a -> b
$ MVar (Either JSVal JSVal) -> IO (Either JSVal JSVal)
forall a. MVar a -> IO a
takeMVar MVar (Either JSVal JSVal)
resultMVar
    Function -> JSM ()
freeFunction Function
success
    Function -> JSM ()
freeFunction Function
error
    case Either JSVal JSVal
result of
        Left JSVal
reason -> do
          Maybe Text
reason' <- JSVal -> JSM (Maybe Text)
forall a. FromJSVal a => JSVal -> JSM (Maybe a)
fromJSVal JSVal
reason
          let reason'' :: String
reason'' = case Maybe Text
reason' of
                Just Text
t -> Text -> String
T.unpack Text
t
                Maybe Text
Nothing -> String
"Unknown reason"
          IO JSVal -> JSM JSVal
forall a. IO a -> JSM a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO JSVal -> JSM JSVal)
-> (PromiseRejected -> IO JSVal) -> PromiseRejected -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PromiseRejected -> IO JSVal
forall e a. Exception e => e -> IO a
throwIO (PromiseRejected -> JSM JSVal) -> PromiseRejected -> JSM JSVal
forall a b. (a -> b) -> a -> b
$ String -> PromiseRejected
PromiseRejected String
reason''
        Right JSVal
x -> JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return JSVal
x

-- Callbacks
newtype Callback a = Callback JSaddle.Function

withCallback :: (MonadDOM m, Coercible c JSaddle.Function)
             => JSM c -> (c -> JSM a) -> m a
withCallback :: forall (m :: * -> *) c a.
(MonadDOM m, Coercible c Function) =>
JSM c -> (c -> JSM a) -> m a
withCallback JSM c
aquire c -> JSM a
f = do
    DOMContext
jsCtx <- m DOMContext
forall (m :: * -> *). MonadDOM m => m DOMContext
askJSM
    IO a -> m a
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$ IO c -> (c -> IO ()) -> (c -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
        (JSM c -> DOMContext -> IO c
forall (m :: * -> *) a. MonadIO m => DOM a -> DOMContext -> m a
runJSM JSM c
aquire DOMContext
jsCtx)
        ((JSM () -> DOMContext -> IO ()
forall (m :: * -> *) a. MonadIO m => DOM a -> DOMContext -> m a
`runJSM` DOMContext
jsCtx) (JSM () -> IO ()) -> (c -> JSM ()) -> c -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Function -> JSM ()
freeFunction (Function -> JSM ()) -> (c -> Function) -> c -> JSM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Function
forall a b. Coercible a b => a -> b
coerce)
        (\c
t -> JSM a -> DOMContext -> IO a
forall (m :: * -> *) a. MonadIO m => DOM a -> DOMContext -> m a
runJSM (c -> JSM a
f c
t) DOMContext
jsCtx)

newtype AudioBufferCallback = AudioBufferCallback (Callback (JSVal -> IO ()))
noAudioBufferCallback :: Maybe AudioBufferCallback
noAudioBufferCallback :: Maybe AudioBufferCallback
noAudioBufferCallback = Maybe AudioBufferCallback
forall a. Maybe a
Nothing
{-# INLINE noAudioBufferCallback #-}
instance ToJSVal AudioBufferCallback where toJSVal :: AudioBufferCallback -> JSM JSVal
toJSVal (AudioBufferCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype BlobCallback = BlobCallback (Callback (JSVal -> IO ()))
noBlobCallback :: Maybe BlobCallback
noBlobCallback :: Maybe BlobCallback
noBlobCallback = Maybe BlobCallback
forall a. Maybe a
Nothing
{-# INLINE noBlobCallback #-}
instance ToJSVal BlobCallback where toJSVal :: BlobCallback -> JSM JSVal
toJSVal (BlobCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype DatabaseCallback = DatabaseCallback (Callback (JSVal -> IO ()))
noDatabaseCallback :: Maybe DatabaseCallback
noDatabaseCallback :: Maybe DatabaseCallback
noDatabaseCallback = Maybe DatabaseCallback
forall a. Maybe a
Nothing
{-# INLINE noDatabaseCallback #-}
instance ToJSVal DatabaseCallback where toJSVal :: DatabaseCallback -> JSM JSVal
toJSVal (DatabaseCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype IntersectionObserverCallback = IntersectionObserverCallback (Callback (JSVal -> JSVal -> IO ()))
noIntersectionObserverCallback :: Maybe IntersectionObserverCallback
noIntersectionObserverCallback :: Maybe IntersectionObserverCallback
noIntersectionObserverCallback = Maybe IntersectionObserverCallback
forall a. Maybe a
Nothing
{-# INLINE noIntersectionObserverCallback #-}
instance ToJSVal IntersectionObserverCallback where toJSVal :: IntersectionObserverCallback -> JSM JSVal
toJSVal (IntersectionObserverCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype MediaQueryListListener = MediaQueryListListener (Callback (JSVal -> IO ()))
noMediaQueryListListener :: Maybe MediaQueryListListener
noMediaQueryListListener :: Maybe MediaQueryListListener
noMediaQueryListListener = Maybe MediaQueryListListener
forall a. Maybe a
Nothing
{-# INLINE noMediaQueryListListener #-}
instance ToJSVal MediaQueryListListener where toJSVal :: MediaQueryListListener -> JSM JSVal
toJSVal (MediaQueryListListener (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype MediaStreamTrackSourcesCallback = MediaStreamTrackSourcesCallback (Callback (JSVal -> IO ()))
noMediaStreamTrackSourcesCallback :: Maybe MediaStreamTrackSourcesCallback
noMediaStreamTrackSourcesCallback :: Maybe MediaStreamTrackSourcesCallback
noMediaStreamTrackSourcesCallback = Maybe MediaStreamTrackSourcesCallback
forall a. Maybe a
Nothing
{-# INLINE noMediaStreamTrackSourcesCallback #-}
instance ToJSVal MediaStreamTrackSourcesCallback where toJSVal :: MediaStreamTrackSourcesCallback -> JSM JSVal
toJSVal (MediaStreamTrackSourcesCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype NavigatorUserMediaErrorCallback = NavigatorUserMediaErrorCallback (Callback (JSVal -> IO ()))
noNavigatorUserMediaErrorCallback :: Maybe NavigatorUserMediaErrorCallback
noNavigatorUserMediaErrorCallback :: Maybe NavigatorUserMediaErrorCallback
noNavigatorUserMediaErrorCallback = Maybe NavigatorUserMediaErrorCallback
forall a. Maybe a
Nothing
{-# INLINE noNavigatorUserMediaErrorCallback #-}
instance ToJSVal NavigatorUserMediaErrorCallback where toJSVal :: NavigatorUserMediaErrorCallback -> JSM JSVal
toJSVal (NavigatorUserMediaErrorCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype NavigatorUserMediaSuccessCallback = NavigatorUserMediaSuccessCallback (Callback (JSVal -> IO ()))
noNavigatorUserMediaSuccessCallback :: Maybe NavigatorUserMediaSuccessCallback
noNavigatorUserMediaSuccessCallback :: Maybe NavigatorUserMediaSuccessCallback
noNavigatorUserMediaSuccessCallback = Maybe NavigatorUserMediaSuccessCallback
forall a. Maybe a
Nothing
{-# INLINE noNavigatorUserMediaSuccessCallback #-}
instance ToJSVal NavigatorUserMediaSuccessCallback where toJSVal :: NavigatorUserMediaSuccessCallback -> JSM JSVal
toJSVal (NavigatorUserMediaSuccessCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype NotificationPermissionCallback permissions = NotificationPermissionCallback (Callback (JSVal -> IO ()))
instance ToJSVal (NotificationPermissionCallback permissions) where toJSVal :: NotificationPermissionCallback permissions -> JSM JSVal
toJSVal (NotificationPermissionCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype NodeFilter = NodeFilter (Callback (JSVal -> IO ()))
noNodeFilter :: Maybe NodeFilter
noNodeFilter :: Maybe NodeFilter
noNodeFilter = Maybe NodeFilter
forall a. Maybe a
Nothing
{-# INLINE noNodeFilter #-}
instance ToJSVal NodeFilter where toJSVal :: NodeFilter -> JSM JSVal
toJSVal (NodeFilter (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype PositionCallback = PositionCallback (Callback (JSVal -> IO ()))
noPositionCallback :: Maybe PositionCallback
noPositionCallback :: Maybe PositionCallback
noPositionCallback = Maybe PositionCallback
forall a. Maybe a
Nothing
{-# INLINE noPositionCallback #-}
instance ToJSVal PositionCallback where toJSVal :: PositionCallback -> JSM JSVal
toJSVal (PositionCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype PositionErrorCallback = PositionErrorCallback (Callback (JSVal -> IO ()))
noPositionErrorCallback :: Maybe PositionErrorCallback
noPositionErrorCallback :: Maybe PositionErrorCallback
noPositionErrorCallback = Maybe PositionErrorCallback
forall a. Maybe a
Nothing
{-# INLINE noPositionErrorCallback #-}
instance ToJSVal PositionErrorCallback where toJSVal :: PositionErrorCallback -> JSM JSVal
toJSVal (PositionErrorCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype PerformanceObserverCallback = PerformanceObserverCallback (Callback (JSVal -> JSVal -> IO ()))
noPerformanceObserverCallback :: Maybe PerformanceObserverCallback
noPerformanceObserverCallback :: Maybe PerformanceObserverCallback
noPerformanceObserverCallback = Maybe PerformanceObserverCallback
forall a. Maybe a
Nothing
{-# INLINE noPerformanceObserverCallback #-}
instance ToJSVal PerformanceObserverCallback where toJSVal :: PerformanceObserverCallback -> JSM JSVal
toJSVal (PerformanceObserverCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype RequestAnimationFrameCallback = RequestAnimationFrameCallback (Callback (JSVal -> IO ()))
noRequestAnimationFrameCallback :: Maybe RequestAnimationFrameCallback
noRequestAnimationFrameCallback :: Maybe RequestAnimationFrameCallback
noRequestAnimationFrameCallback = Maybe RequestAnimationFrameCallback
forall a. Maybe a
Nothing
{-# INLINE noRequestAnimationFrameCallback #-}
instance ToJSVal RequestAnimationFrameCallback where toJSVal :: RequestAnimationFrameCallback -> JSM JSVal
toJSVal (RequestAnimationFrameCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype RTCPeerConnectionErrorCallback = RTCPeerConnectionErrorCallback (Callback (JSVal -> IO ()))
noRTCPeerConnectionErrorCallback :: Maybe RTCPeerConnectionErrorCallback
noRTCPeerConnectionErrorCallback :: Maybe RTCPeerConnectionErrorCallback
noRTCPeerConnectionErrorCallback = Maybe RTCPeerConnectionErrorCallback
forall a. Maybe a
Nothing
{-# INLINE noRTCPeerConnectionErrorCallback #-}
instance ToJSVal RTCPeerConnectionErrorCallback where toJSVal :: RTCPeerConnectionErrorCallback -> JSM JSVal
toJSVal (RTCPeerConnectionErrorCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype RTCSessionDescriptionCallback = RTCSessionDescriptionCallback (Callback (JSVal -> IO ()))
noRTCSessionDescriptionCallback :: Maybe RTCSessionDescriptionCallback
noRTCSessionDescriptionCallback :: Maybe RTCSessionDescriptionCallback
noRTCSessionDescriptionCallback = Maybe RTCSessionDescriptionCallback
forall a. Maybe a
Nothing
{-# INLINE noRTCSessionDescriptionCallback #-}
instance ToJSVal RTCSessionDescriptionCallback where toJSVal :: RTCSessionDescriptionCallback -> JSM JSVal
toJSVal (RTCSessionDescriptionCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype RTCStatsCallback = RTCStatsCallback (Callback (JSVal -> IO ()))
noRTCStatsCallback :: Maybe RTCStatsCallback
noRTCStatsCallback :: Maybe RTCStatsCallback
noRTCStatsCallback = Maybe RTCStatsCallback
forall a. Maybe a
Nothing
{-# INLINE noRTCStatsCallback #-}
instance ToJSVal RTCStatsCallback where toJSVal :: RTCStatsCallback -> JSM JSVal
toJSVal (RTCStatsCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype SQLStatementCallback = SQLStatementCallback (Callback (JSVal -> JSVal -> IO ()))
noSQLStatementCallback :: Maybe SQLStatementCallback
noSQLStatementCallback :: Maybe SQLStatementCallback
noSQLStatementCallback = Maybe SQLStatementCallback
forall a. Maybe a
Nothing
{-# INLINE noSQLStatementCallback #-}
instance ToJSVal SQLStatementCallback where toJSVal :: SQLStatementCallback -> JSM JSVal
toJSVal (SQLStatementCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype SQLStatementErrorCallback = SQLStatementErrorCallback (Callback (JSVal -> JSVal -> IO ()))
noSQLStatementErrorCallback :: Maybe SQLStatementErrorCallback
noSQLStatementErrorCallback :: Maybe SQLStatementErrorCallback
noSQLStatementErrorCallback = Maybe SQLStatementErrorCallback
forall a. Maybe a
Nothing
{-# INLINE noSQLStatementErrorCallback #-}
instance ToJSVal SQLStatementErrorCallback where toJSVal :: SQLStatementErrorCallback -> JSM JSVal
toJSVal (SQLStatementErrorCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype SQLTransactionCallback = SQLTransactionCallback (Callback (JSVal -> IO ()))
noSQLTransactionCallback :: Maybe SQLTransactionCallback
noSQLTransactionCallback :: Maybe SQLTransactionCallback
noSQLTransactionCallback = Maybe SQLTransactionCallback
forall a. Maybe a
Nothing
{-# INLINE noSQLTransactionCallback #-}
instance ToJSVal SQLTransactionCallback where toJSVal :: SQLTransactionCallback -> JSM JSVal
toJSVal (SQLTransactionCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype SQLTransactionErrorCallback = SQLTransactionErrorCallback (Callback (JSVal -> IO ()))
noSQLTransactionErrorCallback :: Maybe SQLTransactionErrorCallback
noSQLTransactionErrorCallback :: Maybe SQLTransactionErrorCallback
noSQLTransactionErrorCallback = Maybe SQLTransactionErrorCallback
forall a. Maybe a
Nothing
{-# INLINE noSQLTransactionErrorCallback #-}
instance ToJSVal SQLTransactionErrorCallback where toJSVal :: SQLTransactionErrorCallback -> JSM JSVal
toJSVal (SQLTransactionErrorCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype StorageErrorCallback = StorageErrorCallback (Callback (JSVal -> IO ()))
noStorageErrorCallback :: Maybe StorageErrorCallback
noStorageErrorCallback :: Maybe StorageErrorCallback
noStorageErrorCallback = Maybe StorageErrorCallback
forall a. Maybe a
Nothing
{-# INLINE noStorageErrorCallback #-}
instance ToJSVal StorageErrorCallback where toJSVal :: StorageErrorCallback -> JSM JSVal
toJSVal (StorageErrorCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype StorageQuotaCallback = StorageQuotaCallback (Callback (JSVal -> IO ()))
noStorageQuotaCallback :: Maybe StorageQuotaCallback
noStorageQuotaCallback :: Maybe StorageQuotaCallback
noStorageQuotaCallback = Maybe StorageQuotaCallback
forall a. Maybe a
Nothing
{-# INLINE noStorageQuotaCallback #-}
instance ToJSVal StorageQuotaCallback where toJSVal :: StorageQuotaCallback -> JSM JSVal
toJSVal (StorageQuotaCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype StorageUsageCallback = StorageUsageCallback (Callback (JSVal -> JSVal -> IO ()))
noStorageUsageCallback :: Maybe StorageUsageCallback
noStorageUsageCallback :: Maybe StorageUsageCallback
noStorageUsageCallback = Maybe StorageUsageCallback
forall a. Maybe a
Nothing
{-# INLINE noStorageUsageCallback #-}
instance ToJSVal StorageUsageCallback where toJSVal :: StorageUsageCallback -> JSM JSVal
toJSVal (StorageUsageCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype StringCallback s = StringCallback (Callback (JSVal -> IO ()))
instance ToJSVal (StringCallback s) where toJSVal :: StringCallback s -> JSM JSVal
toJSVal (StringCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r
newtype VoidCallback = VoidCallback (Callback (IO ()))
noVoidCallback :: Maybe VoidCallback
noVoidCallback :: Maybe VoidCallback
noVoidCallback = Maybe VoidCallback
forall a. Maybe a
Nothing
{-# INLINE noVoidCallback #-}
instance ToJSVal VoidCallback where toJSVal :: VoidCallback -> JSM JSVal
toJSVal (VoidCallback (Callback Function
r)) = Function -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Function
r

-- Custom types
type DOMHighResTimeStamp = Double
noDOMHighResTimeStamp :: Maybe DOMHighResTimeStamp
noDOMHighResTimeStamp :: Maybe Double
noDOMHighResTimeStamp = Maybe Double
forall a. Maybe a
Nothing
{-# INLINE noDOMHighResTimeStamp #-}
type PerformanceEntryList = [PerformanceEntry]
noPerformanceEntryList :: Maybe PerformanceEntryList
noPerformanceEntryList :: Maybe PerformanceEntryList
noPerformanceEntryList = Maybe PerformanceEntryList
forall a. Maybe a
Nothing
{-# INLINE noPerformanceEntryList #-}

-- Record Type
newtype Record key value = Record { forall key value. Record key value -> JSVal
unRecord :: JSVal }

instance PToJSVal (Record key value) where
  pToJSVal :: Record key value -> JSVal
pToJSVal = Record key value -> JSVal
forall key value. Record key value -> JSVal
unRecord
  {-# INLINE pToJSVal #-}

instance PFromJSVal (Record key value) where
  pFromJSVal :: JSVal -> Record key value
pFromJSVal = JSVal -> Record key value
forall key value. JSVal -> Record key value
Record
  {-# INLINE pFromJSVal #-}

instance ToJSVal (Record key value) where
  toJSVal :: Record key value -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Record key value -> JSVal) -> Record key value -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Record key value -> JSVal
forall key value. Record key value -> JSVal
unRecord
  {-# INLINE toJSVal #-}

instance FromJSVal (Record key value) where
  fromJSVal :: JSVal -> JSM (Maybe (Record key value))
fromJSVal JSVal
v = (JSVal -> Record key value)
-> Maybe JSVal -> Maybe (Record key value)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Record key value
forall key value. JSVal -> Record key value
Record (Maybe JSVal -> Maybe (Record key value))
-> JSM (Maybe JSVal) -> JSM (Maybe (Record key value))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM (Record key value)
fromJSValUnchecked = Record key value -> JSM (Record key value)
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Record key value -> JSM (Record key value))
-> (JSVal -> Record key value) -> JSVal -> JSM (Record key value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Record key value
forall key value. JSVal -> Record key value
Record
  {-# INLINE fromJSValUnchecked #-}

newtype SerializedScriptValue = SerializedScriptValue { SerializedScriptValue -> JSVal
unSerializedScriptValue :: JSVal }
noSerializedScriptValue :: Maybe SerializedScriptValue
noSerializedScriptValue :: Maybe SerializedScriptValue
noSerializedScriptValue = Maybe SerializedScriptValue
forall a. Maybe a
Nothing
{-# INLINE noSerializedScriptValue #-}

instance PToJSVal SerializedScriptValue where
  pToJSVal :: SerializedScriptValue -> JSVal
pToJSVal = SerializedScriptValue -> JSVal
unSerializedScriptValue
  {-# INLINE pToJSVal #-}

instance PFromJSVal SerializedScriptValue where
  pFromJSVal :: JSVal -> SerializedScriptValue
pFromJSVal = JSVal -> SerializedScriptValue
SerializedScriptValue
  {-# INLINE pFromJSVal #-}

instance ToJSVal SerializedScriptValue where
  toJSVal :: SerializedScriptValue -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SerializedScriptValue -> JSVal)
-> SerializedScriptValue
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SerializedScriptValue -> JSVal
unSerializedScriptValue
  {-# INLINE toJSVal #-}

instance FromJSVal SerializedScriptValue where
  fromJSVal :: JSVal -> JSM (Maybe SerializedScriptValue)
fromJSVal JSVal
v = (JSVal -> SerializedScriptValue)
-> Maybe JSVal -> Maybe SerializedScriptValue
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SerializedScriptValue
SerializedScriptValue (Maybe JSVal -> Maybe SerializedScriptValue)
-> JSM (Maybe JSVal) -> JSM (Maybe SerializedScriptValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SerializedScriptValue
fromJSValUnchecked = SerializedScriptValue -> JSM SerializedScriptValue
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SerializedScriptValue -> JSM SerializedScriptValue)
-> (JSVal -> SerializedScriptValue)
-> JSVal
-> JSM SerializedScriptValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SerializedScriptValue
SerializedScriptValue
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsSerializedScriptValue o
toSerializedScriptValue :: IsSerializedScriptValue o => o -> SerializedScriptValue
toSerializedScriptValue :: forall o. IsSerializedScriptValue o => o -> SerializedScriptValue
toSerializedScriptValue = JSVal -> SerializedScriptValue
SerializedScriptValue (JSVal -> SerializedScriptValue)
-> (o -> JSVal) -> o -> SerializedScriptValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsSerializedScriptValue SerializedScriptValue
instance IsGObject SerializedScriptValue where
  typeGType :: SerializedScriptValue -> JSM GType
typeGType SerializedScriptValue
_ = String -> JSM GType
forall a. HasCallStack => String -> a
error String
"Unable to get the JavaScript type of SerializedScriptValue"

newtype Dictionary = Dictionary { Dictionary -> JSVal
unDictionary :: JSVal }
noDictionary :: Maybe Dictionary
noDictionary :: Maybe Dictionary
noDictionary = Maybe Dictionary
forall a. Maybe a
Nothing
{-# INLINE noDictionary #-}

instance PToJSVal Dictionary where
  pToJSVal :: Dictionary -> JSVal
pToJSVal = Dictionary -> JSVal
unDictionary
  {-# INLINE pToJSVal #-}

instance PFromJSVal Dictionary where
  pFromJSVal :: JSVal -> Dictionary
pFromJSVal = JSVal -> Dictionary
Dictionary
  {-# INLINE pFromJSVal #-}

instance ToJSVal Dictionary where
  toJSVal :: Dictionary -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Dictionary -> JSVal) -> Dictionary -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dictionary -> JSVal
unDictionary
  {-# INLINE toJSVal #-}

instance FromJSVal Dictionary where
  fromJSVal :: JSVal -> JSM (Maybe Dictionary)
fromJSVal JSVal
v = (JSVal -> Dictionary) -> Maybe JSVal -> Maybe Dictionary
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Dictionary
Dictionary (Maybe JSVal -> Maybe Dictionary)
-> JSM (Maybe JSVal) -> JSM (Maybe Dictionary)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Dictionary
fromJSValUnchecked = Dictionary -> JSM Dictionary
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Dictionary -> JSM Dictionary)
-> (JSVal -> Dictionary) -> JSVal -> JSM Dictionary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Dictionary
Dictionary
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsDictionary o
toDictionary :: IsDictionary o => o -> Dictionary
toDictionary :: forall o. IsDictionary o => o -> Dictionary
toDictionary = JSVal -> Dictionary
Dictionary (JSVal -> Dictionary) -> (o -> JSVal) -> o -> Dictionary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsDictionary Dictionary
instance IsGObject Dictionary where
  typeGType :: Dictionary -> JSM GType
typeGType Dictionary
_ = String -> JSM GType
forall a. HasCallStack => String -> a
error String
"Unable to get the JavaScript type of Dictionary"

newtype MutationCallback = MutationCallback { MutationCallback -> JSVal
unMutationCallback :: JSVal }
noMutationCallback :: Maybe MutationCallback
noMutationCallback :: Maybe MutationCallback
noMutationCallback = Maybe MutationCallback
forall a. Maybe a
Nothing
{-# INLINE noMutationCallback #-}

instance PToJSVal MutationCallback where
  pToJSVal :: MutationCallback -> JSVal
pToJSVal = MutationCallback -> JSVal
unMutationCallback
  {-# INLINE pToJSVal #-}

instance PFromJSVal MutationCallback where
  pFromJSVal :: JSVal -> MutationCallback
pFromJSVal = JSVal -> MutationCallback
MutationCallback
  {-# INLINE pFromJSVal #-}

instance ToJSVal MutationCallback where
  toJSVal :: MutationCallback -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MutationCallback -> JSVal) -> MutationCallback -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutationCallback -> JSVal
unMutationCallback
  {-# INLINE toJSVal #-}

instance FromJSVal MutationCallback where
  fromJSVal :: JSVal -> JSM (Maybe MutationCallback)
fromJSVal JSVal
v = (JSVal -> MutationCallback)
-> Maybe JSVal -> Maybe MutationCallback
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MutationCallback
MutationCallback (Maybe JSVal -> Maybe MutationCallback)
-> JSM (Maybe JSVal) -> JSM (Maybe MutationCallback)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MutationCallback
fromJSValUnchecked = MutationCallback -> JSM MutationCallback
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MutationCallback -> JSM MutationCallback)
-> (JSVal -> MutationCallback) -> JSVal -> JSM MutationCallback
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MutationCallback
MutationCallback
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsMutationCallback o
toMutationCallback :: IsMutationCallback o => o -> MutationCallback
toMutationCallback :: forall o. IsMutationCallback o => o -> MutationCallback
toMutationCallback = JSVal -> MutationCallback
MutationCallback (JSVal -> MutationCallback)
-> (o -> JSVal) -> o -> MutationCallback
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsMutationCallback MutationCallback
instance IsGObject MutationCallback where
  typeGType :: MutationCallback -> JSM GType
typeGType MutationCallback
_ = String -> JSM GType
forall a. HasCallStack => String -> a
error String
"Unable to get the JavaScript type of MutationCallback"

newtype ArrayBuffer = ArrayBuffer { ArrayBuffer -> JSVal
unArrayBuffer :: JSVal }
noArrayBuffer :: Maybe ArrayBuffer
noArrayBuffer :: Maybe ArrayBuffer
noArrayBuffer = Maybe ArrayBuffer
forall a. Maybe a
Nothing
{-# INLINE noArrayBuffer #-}

instance PToJSVal ArrayBuffer where
  pToJSVal :: ArrayBuffer -> JSVal
pToJSVal = ArrayBuffer -> JSVal
unArrayBuffer
  {-# INLINE pToJSVal #-}

instance PFromJSVal ArrayBuffer where
  pFromJSVal :: JSVal -> ArrayBuffer
pFromJSVal = JSVal -> ArrayBuffer
ArrayBuffer
  {-# INLINE pFromJSVal #-}

instance ToJSVal ArrayBuffer where
  toJSVal :: ArrayBuffer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ArrayBuffer -> JSVal) -> ArrayBuffer -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArrayBuffer -> JSVal
unArrayBuffer
  {-# INLINE toJSVal #-}

instance FromJSVal ArrayBuffer where
  fromJSVal :: JSVal -> JSM (Maybe ArrayBuffer)
fromJSVal JSVal
v = (JSVal -> ArrayBuffer) -> Maybe JSVal -> Maybe ArrayBuffer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ArrayBuffer
ArrayBuffer (Maybe JSVal -> Maybe ArrayBuffer)
-> JSM (Maybe JSVal) -> JSM (Maybe ArrayBuffer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ArrayBuffer
fromJSValUnchecked = ArrayBuffer -> JSM ArrayBuffer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ArrayBuffer -> JSM ArrayBuffer)
-> (JSVal -> ArrayBuffer) -> JSVal -> JSM ArrayBuffer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ArrayBuffer
ArrayBuffer
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsArrayBuffer o
toArrayBuffer :: IsArrayBuffer o => o -> ArrayBuffer
toArrayBuffer :: forall o. IsArrayBuffer o => o -> ArrayBuffer
toArrayBuffer = JSVal -> ArrayBuffer
ArrayBuffer (JSVal -> ArrayBuffer) -> (o -> JSVal) -> o -> ArrayBuffer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsArrayBuffer ArrayBuffer
instance IsGObject ArrayBuffer where
    typeGType :: ArrayBuffer -> JSM GType
typeGType ArrayBuffer
_ = JSM GType
gTypeArrayBuffer

gTypeArrayBuffer :: JSM GType
gTypeArrayBuffer :: JSM GType
gTypeArrayBuffer = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ArrayBuffer"

newtype Float32Array = Float32Array { Float32Array -> JSVal
unFloat32Array :: JSVal }
noFloat32Array :: Maybe Float32Array
noFloat32Array :: Maybe Float32Array
noFloat32Array = Maybe Float32Array
forall a. Maybe a
Nothing
{-# INLINE noFloat32Array #-}

instance PToJSVal Float32Array where
  pToJSVal :: Float32Array -> JSVal
pToJSVal = Float32Array -> JSVal
unFloat32Array
  {-# INLINE pToJSVal #-}

instance PFromJSVal Float32Array where
  pFromJSVal :: JSVal -> Float32Array
pFromJSVal = JSVal -> Float32Array
Float32Array
  {-# INLINE pFromJSVal #-}

instance ToJSVal Float32Array where
  toJSVal :: Float32Array -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Float32Array -> JSVal) -> Float32Array -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float32Array -> JSVal
unFloat32Array
  {-# INLINE toJSVal #-}

instance FromJSVal Float32Array where
  fromJSVal :: JSVal -> JSM (Maybe Float32Array)
fromJSVal JSVal
v = (JSVal -> Float32Array) -> Maybe JSVal -> Maybe Float32Array
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Float32Array
Float32Array (Maybe JSVal -> Maybe Float32Array)
-> JSM (Maybe JSVal) -> JSM (Maybe Float32Array)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Float32Array
fromJSValUnchecked = Float32Array -> JSM Float32Array
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Float32Array -> JSM Float32Array)
-> (JSVal -> Float32Array) -> JSVal -> JSM Float32Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Float32Array
Float32Array
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsFloat32Array o
toFloat32Array :: IsFloat32Array o => o -> Float32Array
toFloat32Array :: forall o. IsFloat32Array o => o -> Float32Array
toFloat32Array = JSVal -> Float32Array
Float32Array (JSVal -> Float32Array) -> (o -> JSVal) -> o -> Float32Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsFloat32Array Float32Array
instance IsGObject Float32Array where
        typeGType :: Float32Array -> JSM GType
typeGType Float32Array
_ = JSM GType
gTypeFloat32Array

gTypeFloat32Array :: JSM GType
gTypeFloat32Array :: JSM GType
gTypeFloat32Array = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Float32Array"

newtype Float64Array = Float64Array { Float64Array -> JSVal
unFloat64Array :: JSVal }
noFloat64Array :: Maybe Float64Array
noFloat64Array :: Maybe Float64Array
noFloat64Array = Maybe Float64Array
forall a. Maybe a
Nothing
{-# INLINE noFloat64Array #-}

instance PToJSVal Float64Array where
  pToJSVal :: Float64Array -> JSVal
pToJSVal = Float64Array -> JSVal
unFloat64Array
  {-# INLINE pToJSVal #-}

instance PFromJSVal Float64Array where
  pFromJSVal :: JSVal -> Float64Array
pFromJSVal = JSVal -> Float64Array
Float64Array
  {-# INLINE pFromJSVal #-}

instance ToJSVal Float64Array where
  toJSVal :: Float64Array -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Float64Array -> JSVal) -> Float64Array -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float64Array -> JSVal
unFloat64Array
  {-# INLINE toJSVal #-}

instance FromJSVal Float64Array where
  fromJSVal :: JSVal -> JSM (Maybe Float64Array)
fromJSVal JSVal
v = (JSVal -> Float64Array) -> Maybe JSVal -> Maybe Float64Array
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Float64Array
Float64Array (Maybe JSVal -> Maybe Float64Array)
-> JSM (Maybe JSVal) -> JSM (Maybe Float64Array)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Float64Array
fromJSValUnchecked = Float64Array -> JSM Float64Array
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Float64Array -> JSM Float64Array)
-> (JSVal -> Float64Array) -> JSVal -> JSM Float64Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Float64Array
Float64Array
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsFloat64Array o
toFloat64Array :: IsFloat64Array o => o -> Float64Array
toFloat64Array :: forall o. IsFloat64Array o => o -> Float64Array
toFloat64Array = JSVal -> Float64Array
Float64Array (JSVal -> Float64Array) -> (o -> JSVal) -> o -> Float64Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsFloat64Array Float64Array
instance IsGObject Float64Array where
    typeGType :: Float64Array -> JSM GType
typeGType Float64Array
_ = JSM GType
gTypeFloat64Array

gTypeFloat64Array :: JSM GType
gTypeFloat64Array :: JSM GType
gTypeFloat64Array = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Float64Array"

newtype Uint8Array = Uint8Array { Uint8Array -> JSVal
unUint8Array :: JSVal }
noUint8Array :: Maybe Uint8Array
noUint8Array :: Maybe Uint8Array
noUint8Array = Maybe Uint8Array
forall a. Maybe a
Nothing
{-# INLINE noUint8Array #-}

instance PToJSVal Uint8Array where
  pToJSVal :: Uint8Array -> JSVal
pToJSVal = Uint8Array -> JSVal
unUint8Array
  {-# INLINE pToJSVal #-}

instance PFromJSVal Uint8Array where
  pFromJSVal :: JSVal -> Uint8Array
pFromJSVal = JSVal -> Uint8Array
Uint8Array
  {-# INLINE pFromJSVal #-}

instance ToJSVal Uint8Array where
  toJSVal :: Uint8Array -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Uint8Array -> JSVal) -> Uint8Array -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Uint8Array -> JSVal
unUint8Array
  {-# INLINE toJSVal #-}

instance FromJSVal Uint8Array where
  fromJSVal :: JSVal -> JSM (Maybe Uint8Array)
fromJSVal JSVal
v = (JSVal -> Uint8Array) -> Maybe JSVal -> Maybe Uint8Array
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Uint8Array
Uint8Array (Maybe JSVal -> Maybe Uint8Array)
-> JSM (Maybe JSVal) -> JSM (Maybe Uint8Array)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Uint8Array
fromJSValUnchecked = Uint8Array -> JSM Uint8Array
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Uint8Array -> JSM Uint8Array)
-> (JSVal -> Uint8Array) -> JSVal -> JSM Uint8Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Uint8Array
Uint8Array
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsUint8Array o
toUint8Array :: IsUint8Array o => o -> Uint8Array
toUint8Array :: forall o. IsUint8Array o => o -> Uint8Array
toUint8Array = JSVal -> Uint8Array
Uint8Array (JSVal -> Uint8Array) -> (o -> JSVal) -> o -> Uint8Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsUint8Array Uint8Array
instance IsGObject Uint8Array where
    typeGType :: Uint8Array -> JSM GType
typeGType Uint8Array
_ = JSM GType
gTypeUint8Array

gTypeUint8Array :: JSM GType
gTypeUint8Array :: JSM GType
gTypeUint8Array = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Uint8Array"

newtype Uint8ClampedArray = Uint8ClampedArray { Uint8ClampedArray -> JSVal
unUint8ClampedArray :: JSVal }
noUint8ClampedArray :: Maybe Uint8ClampedArray
noUint8ClampedArray :: Maybe Uint8ClampedArray
noUint8ClampedArray = Maybe Uint8ClampedArray
forall a. Maybe a
Nothing
{-# INLINE noUint8ClampedArray #-}

instance PToJSVal Uint8ClampedArray where
  pToJSVal :: Uint8ClampedArray -> JSVal
pToJSVal = Uint8ClampedArray -> JSVal
unUint8ClampedArray
  {-# INLINE pToJSVal #-}

instance PFromJSVal Uint8ClampedArray where
  pFromJSVal :: JSVal -> Uint8ClampedArray
pFromJSVal = JSVal -> Uint8ClampedArray
Uint8ClampedArray
  {-# INLINE pFromJSVal #-}

instance ToJSVal Uint8ClampedArray where
  toJSVal :: Uint8ClampedArray -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Uint8ClampedArray -> JSVal) -> Uint8ClampedArray -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Uint8ClampedArray -> JSVal
unUint8ClampedArray
  {-# INLINE toJSVal #-}

instance FromJSVal Uint8ClampedArray where
  fromJSVal :: JSVal -> JSM (Maybe Uint8ClampedArray)
fromJSVal JSVal
v = (JSVal -> Uint8ClampedArray)
-> Maybe JSVal -> Maybe Uint8ClampedArray
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Uint8ClampedArray
Uint8ClampedArray (Maybe JSVal -> Maybe Uint8ClampedArray)
-> JSM (Maybe JSVal) -> JSM (Maybe Uint8ClampedArray)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Uint8ClampedArray
fromJSValUnchecked = Uint8ClampedArray -> JSM Uint8ClampedArray
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Uint8ClampedArray -> JSM Uint8ClampedArray)
-> (JSVal -> Uint8ClampedArray) -> JSVal -> JSM Uint8ClampedArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Uint8ClampedArray
Uint8ClampedArray
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsUint8ClampedArray o
toUint8ClampedArray :: IsUint8ClampedArray o => o -> Uint8ClampedArray
toUint8ClampedArray :: forall o. IsUint8ClampedArray o => o -> Uint8ClampedArray
toUint8ClampedArray = JSVal -> Uint8ClampedArray
Uint8ClampedArray (JSVal -> Uint8ClampedArray)
-> (o -> JSVal) -> o -> Uint8ClampedArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsUint8ClampedArray Uint8ClampedArray
instance IsGObject Uint8ClampedArray where
    typeGType :: Uint8ClampedArray -> JSM GType
typeGType Uint8ClampedArray
_ = JSM GType
gTypeUint8ClampedArray

gTypeUint8ClampedArray :: JSM GType
gTypeUint8ClampedArray :: JSM GType
gTypeUint8ClampedArray = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Uint8ClampedArray"

newtype Uint16Array = Uint16Array { Uint16Array -> JSVal
unUint16Array :: JSVal }
noUint16Array :: Maybe Uint16Array
noUint16Array :: Maybe Uint16Array
noUint16Array = Maybe Uint16Array
forall a. Maybe a
Nothing
{-# INLINE noUint16Array #-}

instance PToJSVal Uint16Array where
  pToJSVal :: Uint16Array -> JSVal
pToJSVal = Uint16Array -> JSVal
unUint16Array
  {-# INLINE pToJSVal #-}

instance PFromJSVal Uint16Array where
  pFromJSVal :: JSVal -> Uint16Array
pFromJSVal = JSVal -> Uint16Array
Uint16Array
  {-# INLINE pFromJSVal #-}

instance ToJSVal Uint16Array where
  toJSVal :: Uint16Array -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Uint16Array -> JSVal) -> Uint16Array -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Uint16Array -> JSVal
unUint16Array
  {-# INLINE toJSVal #-}

instance FromJSVal Uint16Array where
  fromJSVal :: JSVal -> JSM (Maybe Uint16Array)
fromJSVal JSVal
v = (JSVal -> Uint16Array) -> Maybe JSVal -> Maybe Uint16Array
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Uint16Array
Uint16Array (Maybe JSVal -> Maybe Uint16Array)
-> JSM (Maybe JSVal) -> JSM (Maybe Uint16Array)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Uint16Array
fromJSValUnchecked = Uint16Array -> JSM Uint16Array
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Uint16Array -> JSM Uint16Array)
-> (JSVal -> Uint16Array) -> JSVal -> JSM Uint16Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Uint16Array
Uint16Array
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsUint16Array o
toUint16Array :: IsUint16Array o => o -> Uint16Array
toUint16Array :: forall o. IsUint16Array o => o -> Uint16Array
toUint16Array = JSVal -> Uint16Array
Uint16Array (JSVal -> Uint16Array) -> (o -> JSVal) -> o -> Uint16Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsUint16Array Uint16Array
instance IsGObject Uint16Array where
    typeGType :: Uint16Array -> JSM GType
typeGType Uint16Array
_ = JSM GType
gTypeUint16Array

gTypeUint16Array :: JSM GType
gTypeUint16Array :: JSM GType
gTypeUint16Array = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Uint16Array"

newtype Uint32Array = Uint32Array { Uint32Array -> JSVal
unUint32Array :: JSVal }
noUint32Array :: Maybe Uint32Array
noUint32Array :: Maybe Uint32Array
noUint32Array = Maybe Uint32Array
forall a. Maybe a
Nothing
{-# INLINE noUint32Array #-}

instance PToJSVal Uint32Array where
  pToJSVal :: Uint32Array -> JSVal
pToJSVal = Uint32Array -> JSVal
unUint32Array
  {-# INLINE pToJSVal #-}

instance PFromJSVal Uint32Array where
  pFromJSVal :: JSVal -> Uint32Array
pFromJSVal = JSVal -> Uint32Array
Uint32Array
  {-# INLINE pFromJSVal #-}

instance ToJSVal Uint32Array where
  toJSVal :: Uint32Array -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Uint32Array -> JSVal) -> Uint32Array -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Uint32Array -> JSVal
unUint32Array
  {-# INLINE toJSVal #-}

instance FromJSVal Uint32Array where
  fromJSVal :: JSVal -> JSM (Maybe Uint32Array)
fromJSVal JSVal
v = (JSVal -> Uint32Array) -> Maybe JSVal -> Maybe Uint32Array
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Uint32Array
Uint32Array (Maybe JSVal -> Maybe Uint32Array)
-> JSM (Maybe JSVal) -> JSM (Maybe Uint32Array)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Uint32Array
fromJSValUnchecked = Uint32Array -> JSM Uint32Array
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Uint32Array -> JSM Uint32Array)
-> (JSVal -> Uint32Array) -> JSVal -> JSM Uint32Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Uint32Array
Uint32Array
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsUint32Array o
toUint32Array :: IsUint32Array o => o -> Uint32Array
toUint32Array :: forall o. IsUint32Array o => o -> Uint32Array
toUint32Array = JSVal -> Uint32Array
Uint32Array (JSVal -> Uint32Array) -> (o -> JSVal) -> o -> Uint32Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsUint32Array Uint32Array
instance IsGObject Uint32Array where
    typeGType :: Uint32Array -> JSM GType
typeGType Uint32Array
_ = JSM GType
gTypeUint32Array

gTypeUint32Array :: JSM GType
gTypeUint32Array :: JSM GType
gTypeUint32Array = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Uint32Array"

newtype Int8Array = Int8Array { Int8Array -> JSVal
unInt8Array :: JSVal }
noInt8Array :: Maybe Int8Array
noInt8Array :: Maybe Int8Array
noInt8Array = Maybe Int8Array
forall a. Maybe a
Nothing
{-# INLINE noInt8Array #-}

instance PToJSVal Int8Array where
  pToJSVal :: Int8Array -> JSVal
pToJSVal = Int8Array -> JSVal
unInt8Array
  {-# INLINE pToJSVal #-}

instance PFromJSVal Int8Array where
  pFromJSVal :: JSVal -> Int8Array
pFromJSVal = JSVal -> Int8Array
Int8Array
  {-# INLINE pFromJSVal #-}

instance ToJSVal Int8Array where
  toJSVal :: Int8Array -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Int8Array -> JSVal) -> Int8Array -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8Array -> JSVal
unInt8Array
  {-# INLINE toJSVal #-}

instance FromJSVal Int8Array where
  fromJSVal :: JSVal -> JSM (Maybe Int8Array)
fromJSVal JSVal
v = (JSVal -> Int8Array) -> Maybe JSVal -> Maybe Int8Array
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Int8Array
Int8Array (Maybe JSVal -> Maybe Int8Array)
-> JSM (Maybe JSVal) -> JSM (Maybe Int8Array)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Int8Array
fromJSValUnchecked = Int8Array -> JSM Int8Array
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int8Array -> JSM Int8Array)
-> (JSVal -> Int8Array) -> JSVal -> JSM Int8Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Int8Array
Int8Array
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsInt8Array o
toInt8Array :: IsInt8Array o => o -> Int8Array
toInt8Array :: forall o. IsInt8Array o => o -> Int8Array
toInt8Array = JSVal -> Int8Array
Int8Array (JSVal -> Int8Array) -> (o -> JSVal) -> o -> Int8Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsInt8Array Int8Array
instance IsGObject Int8Array where
    typeGType :: Int8Array -> JSM GType
typeGType Int8Array
_ = JSM GType
gTypeInt8Array

gTypeInt8Array :: JSM GType
gTypeInt8Array :: JSM GType
gTypeInt8Array = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Int8Array"

newtype Int16Array = Int16Array { Int16Array -> JSVal
unInt16Array :: JSVal }
noInt16Array :: Maybe Int16Array
noInt16Array :: Maybe Int16Array
noInt16Array = Maybe Int16Array
forall a. Maybe a
Nothing
{-# INLINE noInt16Array #-}

instance PToJSVal Int16Array where
  pToJSVal :: Int16Array -> JSVal
pToJSVal = Int16Array -> JSVal
unInt16Array
  {-# INLINE pToJSVal #-}

instance PFromJSVal Int16Array where
  pFromJSVal :: JSVal -> Int16Array
pFromJSVal = JSVal -> Int16Array
Int16Array
  {-# INLINE pFromJSVal #-}

instance ToJSVal Int16Array where
  toJSVal :: Int16Array -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Int16Array -> JSVal) -> Int16Array -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16Array -> JSVal
unInt16Array
  {-# INLINE toJSVal #-}

instance FromJSVal Int16Array where
  fromJSVal :: JSVal -> JSM (Maybe Int16Array)
fromJSVal JSVal
v = (JSVal -> Int16Array) -> Maybe JSVal -> Maybe Int16Array
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Int16Array
Int16Array (Maybe JSVal -> Maybe Int16Array)
-> JSM (Maybe JSVal) -> JSM (Maybe Int16Array)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Int16Array
fromJSValUnchecked = Int16Array -> JSM Int16Array
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int16Array -> JSM Int16Array)
-> (JSVal -> Int16Array) -> JSVal -> JSM Int16Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Int16Array
Int16Array
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsInt16Array o
toInt16Array :: IsInt16Array o => o -> Int16Array
toInt16Array :: forall o. IsInt16Array o => o -> Int16Array
toInt16Array = JSVal -> Int16Array
Int16Array (JSVal -> Int16Array) -> (o -> JSVal) -> o -> Int16Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsInt16Array Int16Array
instance IsGObject Int16Array where
    typeGType :: Int16Array -> JSM GType
typeGType Int16Array
_ = JSM GType
gTypeInt16Array

gTypeInt16Array :: JSM GType
gTypeInt16Array :: JSM GType
gTypeInt16Array = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Int16Array"

newtype Int32Array = Int32Array { Int32Array -> JSVal
unInt32Array :: JSVal }
noInt32Array :: Maybe Int32Array
noInt32Array :: Maybe Int32Array
noInt32Array = Maybe Int32Array
forall a. Maybe a
Nothing
{-# INLINE noInt32Array #-}

instance PToJSVal Int32Array where
  pToJSVal :: Int32Array -> JSVal
pToJSVal = Int32Array -> JSVal
unInt32Array
  {-# INLINE pToJSVal #-}

instance PFromJSVal Int32Array where
  pFromJSVal :: JSVal -> Int32Array
pFromJSVal = JSVal -> Int32Array
Int32Array
  {-# INLINE pFromJSVal #-}

instance ToJSVal Int32Array where
  toJSVal :: Int32Array -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Int32Array -> JSVal) -> Int32Array -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32Array -> JSVal
unInt32Array
  {-# INLINE toJSVal #-}

instance FromJSVal Int32Array where
  fromJSVal :: JSVal -> JSM (Maybe Int32Array)
fromJSVal JSVal
v = (JSVal -> Int32Array) -> Maybe JSVal -> Maybe Int32Array
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Int32Array
Int32Array (Maybe JSVal -> Maybe Int32Array)
-> JSM (Maybe JSVal) -> JSM (Maybe Int32Array)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Int32Array
fromJSValUnchecked = Int32Array -> JSM Int32Array
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32Array -> JSM Int32Array)
-> (JSVal -> Int32Array) -> JSVal -> JSM Int32Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Int32Array
Int32Array
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsInt32Array o
toInt32Array :: IsInt32Array o => o -> Int32Array
toInt32Array :: forall o. IsInt32Array o => o -> Int32Array
toInt32Array = JSVal -> Int32Array
Int32Array (JSVal -> Int32Array) -> (o -> JSVal) -> o -> Int32Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsInt32Array Int32Array
instance IsGObject Int32Array where
    typeGType :: Int32Array -> JSM GType
typeGType Int32Array
_ = JSM GType
gTypeInt32Array

gTypeInt32Array :: JSM GType
gTypeInt32Array :: JSM GType
gTypeInt32Array = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Int32Array"

newtype ObjectArray = ObjectArray { ObjectArray -> JSVal
unObjectArray :: JSVal }
noObjectArray :: Maybe ObjectArray
noObjectArray :: Maybe ObjectArray
noObjectArray = Maybe ObjectArray
forall a. Maybe a
Nothing
{-# INLINE noObjectArray #-}

instance PToJSVal ObjectArray where
  pToJSVal :: ObjectArray -> JSVal
pToJSVal = ObjectArray -> JSVal
unObjectArray
  {-# INLINE pToJSVal #-}

instance PFromJSVal ObjectArray where
  pFromJSVal :: JSVal -> ObjectArray
pFromJSVal = JSVal -> ObjectArray
ObjectArray
  {-# INLINE pFromJSVal #-}

instance ToJSVal ObjectArray where
  toJSVal :: ObjectArray -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ObjectArray -> JSVal) -> ObjectArray -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectArray -> JSVal
unObjectArray
  {-# INLINE toJSVal #-}

instance FromJSVal ObjectArray where
  fromJSVal :: JSVal -> JSM (Maybe ObjectArray)
fromJSVal JSVal
v = (JSVal -> ObjectArray) -> Maybe JSVal -> Maybe ObjectArray
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ObjectArray
ObjectArray (Maybe JSVal -> Maybe ObjectArray)
-> JSM (Maybe JSVal) -> JSM (Maybe ObjectArray)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ObjectArray
fromJSValUnchecked = ObjectArray -> JSM ObjectArray
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ObjectArray -> JSM ObjectArray)
-> (JSVal -> ObjectArray) -> JSVal -> JSM ObjectArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ObjectArray
ObjectArray
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsObjectArray o
toObjectArray :: IsObjectArray o => o -> ObjectArray
toObjectArray :: forall o. IsObjectArray o => o -> ObjectArray
toObjectArray = JSVal -> ObjectArray
ObjectArray (JSVal -> ObjectArray) -> (o -> JSVal) -> o -> ObjectArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsObjectArray ObjectArray
instance IsGObject ObjectArray where
  typeGType :: ObjectArray -> JSM GType
typeGType ObjectArray
_ = String -> JSM GType
forall a. HasCallStack => String -> a
error String
"Unable to get the JavaScript type of ObjectArray"

newtype ArrayBufferView = ArrayBufferView { ArrayBufferView -> JSVal
unArrayBufferView :: JSVal }
noArrayBufferView :: Maybe ArrayBufferView
noArrayBufferView :: Maybe ArrayBufferView
noArrayBufferView = Maybe ArrayBufferView
forall a. Maybe a
Nothing
{-# INLINE noArrayBufferView #-}

instance PToJSVal ArrayBufferView where
  pToJSVal :: ArrayBufferView -> JSVal
pToJSVal = ArrayBufferView -> JSVal
unArrayBufferView
  {-# INLINE pToJSVal #-}

instance PFromJSVal ArrayBufferView where
  pFromJSVal :: JSVal -> ArrayBufferView
pFromJSVal = JSVal -> ArrayBufferView
ArrayBufferView
  {-# INLINE pFromJSVal #-}

instance ToJSVal ArrayBufferView where
  toJSVal :: ArrayBufferView -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ArrayBufferView -> JSVal) -> ArrayBufferView -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArrayBufferView -> JSVal
unArrayBufferView
  {-# INLINE toJSVal #-}

instance FromJSVal ArrayBufferView where
  fromJSVal :: JSVal -> JSM (Maybe ArrayBufferView)
fromJSVal JSVal
v = (JSVal -> ArrayBufferView) -> Maybe JSVal -> Maybe ArrayBufferView
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ArrayBufferView
ArrayBufferView (Maybe JSVal -> Maybe ArrayBufferView)
-> JSM (Maybe JSVal) -> JSM (Maybe ArrayBufferView)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ArrayBufferView
fromJSValUnchecked = ArrayBufferView -> JSM ArrayBufferView
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ArrayBufferView -> JSM ArrayBufferView)
-> (JSVal -> ArrayBufferView) -> JSVal -> JSM ArrayBufferView
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ArrayBufferView
ArrayBufferView
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsArrayBufferView o
toArrayBufferView :: IsArrayBufferView o => o -> ArrayBufferView
toArrayBufferView :: forall o. IsArrayBufferView o => o -> ArrayBufferView
toArrayBufferView = JSVal -> ArrayBufferView
ArrayBufferView (JSVal -> ArrayBufferView) -> (o -> JSVal) -> o -> ArrayBufferView
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsArrayBufferView ArrayBufferView
instance IsGObject ArrayBufferView where
  typeGType :: ArrayBufferView -> JSM GType
typeGType ArrayBufferView
_ = String -> JSM GType
forall a. HasCallStack => String -> a
error String
"Unable to get the JavaScript type of ArrayBufferView"

newtype Array = Array { Array -> JSVal
unArray :: JSVal }
noArray :: Maybe Array
noArray :: Maybe Array
noArray = Maybe Array
forall a. Maybe a
Nothing
{-# INLINE noArray #-}

instance PToJSVal Array where
  pToJSVal :: Array -> JSVal
pToJSVal = Array -> JSVal
unArray
  {-# INLINE pToJSVal #-}

instance PFromJSVal Array where
  pFromJSVal :: JSVal -> Array
pFromJSVal = JSVal -> Array
Array
  {-# INLINE pFromJSVal #-}

instance ToJSVal Array where
  toJSVal :: Array -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Array -> JSVal) -> Array -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> JSVal
unArray
  {-# INLINE toJSVal #-}

instance FromJSVal Array where
  fromJSVal :: JSVal -> JSM (Maybe Array)
fromJSVal JSVal
v = (JSVal -> Array) -> Maybe JSVal -> Maybe Array
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Array
Array (Maybe JSVal -> Maybe Array)
-> JSM (Maybe JSVal) -> JSM (Maybe Array)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Array
fromJSValUnchecked = Array -> JSM Array
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Array -> JSM Array) -> (JSVal -> Array) -> JSVal -> JSM Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Array
Array
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsArray o
toArray :: IsArray o => o -> Array
toArray :: forall o. IsArray o => o -> Array
toArray = JSVal -> Array
Array (JSVal -> Array) -> (o -> JSVal) -> o -> Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsArray Array
instance IsGObject Array where
    typeGType :: Array -> JSM GType
typeGType Array
_ = JSM GType
gTypeArray

gTypeArray :: JSM GType
gTypeArray :: JSM GType
gTypeArray = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Array"

newtype Date = Date { Date -> JSVal
unDate :: JSVal }
noDate :: Maybe Date
noDate :: Maybe Date
noDate = Maybe Date
forall a. Maybe a
Nothing
{-# INLINE noDate #-}

instance PToJSVal Date where
  pToJSVal :: Date -> JSVal
pToJSVal = Date -> JSVal
unDate
  {-# INLINE pToJSVal #-}

instance PFromJSVal Date where
  pFromJSVal :: JSVal -> Date
pFromJSVal = JSVal -> Date
Date
  {-# INLINE pFromJSVal #-}

instance ToJSVal Date where
  toJSVal :: Date -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Date -> JSVal) -> Date -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Date -> JSVal
unDate
  {-# INLINE toJSVal #-}

instance FromJSVal Date where
  fromJSVal :: JSVal -> JSM (Maybe Date)
fromJSVal JSVal
v = (JSVal -> Date) -> Maybe JSVal -> Maybe Date
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Date
Date (Maybe JSVal -> Maybe Date)
-> JSM (Maybe JSVal) -> JSM (Maybe Date)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Date
fromJSValUnchecked = Date -> JSM Date
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Date -> JSM Date) -> (JSVal -> Date) -> JSVal -> JSM Date
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Date
Date
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsDate o
toDate :: IsDate o => o -> Date
toDate :: forall o. IsDate o => o -> Date
toDate = JSVal -> Date
Date (JSVal -> Date) -> (o -> JSVal) -> o -> Date
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsDate Date
instance IsGObject Date where
    typeGType :: Date -> JSM GType
typeGType Date
_ = JSM GType
gTypeDate

gTypeDate :: JSM GType
gTypeDate :: JSM GType
gTypeDate = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Date"

newtype Algorithm = Algorithm { Algorithm -> JSVal
unAlgorithm :: JSVal }
noAlgorithm :: Maybe Algorithm
noAlgorithm :: Maybe Algorithm
noAlgorithm = Maybe Algorithm
forall a. Maybe a
Nothing
{-# INLINE noAlgorithm #-}

instance PToJSVal Algorithm where
  pToJSVal :: Algorithm -> JSVal
pToJSVal = Algorithm -> JSVal
unAlgorithm
  {-# INLINE pToJSVal #-}

instance PFromJSVal Algorithm where
  pFromJSVal :: JSVal -> Algorithm
pFromJSVal = JSVal -> Algorithm
Algorithm
  {-# INLINE pFromJSVal #-}

instance ToJSVal Algorithm where
  toJSVal :: Algorithm -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Algorithm -> JSVal) -> Algorithm -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Algorithm -> JSVal
unAlgorithm
  {-# INLINE toJSVal #-}

instance FromJSVal Algorithm where
  fromJSVal :: JSVal -> JSM (Maybe Algorithm)
fromJSVal JSVal
v = (JSVal -> Algorithm) -> Maybe JSVal -> Maybe Algorithm
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Algorithm
Algorithm (Maybe JSVal -> Maybe Algorithm)
-> JSM (Maybe JSVal) -> JSM (Maybe Algorithm)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Algorithm
fromJSValUnchecked = Algorithm -> JSM Algorithm
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Algorithm -> JSM Algorithm)
-> (JSVal -> Algorithm) -> JSVal -> JSM Algorithm
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Algorithm
Algorithm
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsAlgorithm o
toAlgorithm :: IsAlgorithm o => o -> Algorithm
toAlgorithm :: forall o. IsAlgorithm o => o -> Algorithm
toAlgorithm = JSVal -> Algorithm
Algorithm (JSVal -> Algorithm) -> (o -> JSVal) -> o -> Algorithm
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsAlgorithm Algorithm
instance IsGObject Algorithm where
  typeGType :: Algorithm -> JSM GType
typeGType Algorithm
_ = String -> JSM GType
forall a. HasCallStack => String -> a
error String
"Unable to get the JavaScript type of Algorithm"

newtype CryptoOperationData = CryptoOperationData { CryptoOperationData -> JSVal
unCryptoOperationData :: JSVal }
noCryptoOperationData :: Maybe CryptoOperationData
noCryptoOperationData :: Maybe CryptoOperationData
noCryptoOperationData = Maybe CryptoOperationData
forall a. Maybe a
Nothing
{-# INLINE noCryptoOperationData #-}

instance PToJSVal CryptoOperationData where
  pToJSVal :: CryptoOperationData -> JSVal
pToJSVal = CryptoOperationData -> JSVal
unCryptoOperationData
  {-# INLINE pToJSVal #-}

instance PFromJSVal CryptoOperationData where
  pFromJSVal :: JSVal -> CryptoOperationData
pFromJSVal = JSVal -> CryptoOperationData
CryptoOperationData
  {-# INLINE pFromJSVal #-}

instance ToJSVal CryptoOperationData where
  toJSVal :: CryptoOperationData -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CryptoOperationData -> JSVal)
-> CryptoOperationData
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CryptoOperationData -> JSVal
unCryptoOperationData
  {-# INLINE toJSVal #-}

instance FromJSVal CryptoOperationData where
  fromJSVal :: JSVal -> JSM (Maybe CryptoOperationData)
fromJSVal JSVal
v = (JSVal -> CryptoOperationData)
-> Maybe JSVal -> Maybe CryptoOperationData
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CryptoOperationData
CryptoOperationData (Maybe JSVal -> Maybe CryptoOperationData)
-> JSM (Maybe JSVal) -> JSM (Maybe CryptoOperationData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CryptoOperationData
fromJSValUnchecked = CryptoOperationData -> JSM CryptoOperationData
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CryptoOperationData -> JSM CryptoOperationData)
-> (JSVal -> CryptoOperationData)
-> JSVal
-> JSM CryptoOperationData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CryptoOperationData
CryptoOperationData
  {-# INLINE fromJSValUnchecked #-}

class IsGObject o => IsCryptoOperationData o
toCryptoOperationData :: IsCryptoOperationData o => o -> CryptoOperationData
toCryptoOperationData :: forall o. IsCryptoOperationData o => o -> CryptoOperationData
toCryptoOperationData = JSVal -> CryptoOperationData
CryptoOperationData (JSVal -> CryptoOperationData)
-> (o -> JSVal) -> o -> CryptoOperationData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsCryptoOperationData CryptoOperationData
instance IsGObject CryptoOperationData where
  typeGType :: CryptoOperationData -> JSM GType
typeGType CryptoOperationData
_ = String -> JSM GType
forall a. HasCallStack => String -> a
error String
"Unable to get the JavaScript type of CryptoOperationData"
instance IsCryptoOperationData ArrayBuffer
instance IsCryptoOperationData ArrayBufferView

type GLenum = Word32
noGLenum :: Maybe GLenum
noGLenum :: Maybe GLenum
noGLenum = Maybe GLenum
forall a. Maybe a
Nothing
{-# INLINE noGLenum #-}
type GLboolean = Bool
noGLboolean :: Maybe GLboolean
noGLboolean :: Maybe Bool
noGLboolean = Maybe Bool
forall a. Maybe a
Nothing
{-# INLINE noGLboolean #-}
type GLbitfield = Word32
noGLbitfield :: Maybe GLbitfield
noGLbitfield :: Maybe GLenum
noGLbitfield = Maybe GLenum
forall a. Maybe a
Nothing
{-# INLINE noGLbitfield #-}
type GLbyte = Int8
noGLbyte :: Maybe GLbyte
noGLbyte :: Maybe GLbyte
noGLbyte = Maybe GLbyte
forall a. Maybe a
Nothing
{-# INLINE noGLbyte #-}
type GLshort = Int16
noGLshort :: Maybe GLshort
noGLshort :: Maybe GLshort
noGLshort = Maybe GLshort
forall a. Maybe a
Nothing
{-# INLINE noGLshort #-}
type GLint = Int32
noGLint :: Maybe GLint
noGLint :: Maybe GLint
noGLint = Maybe GLint
forall a. Maybe a
Nothing
{-# INLINE noGLint #-}
type GLint64 = Int64
noGLint64 :: Maybe GLint64
noGLint64 :: Maybe GLint64
noGLint64 = Maybe GLint64
forall a. Maybe a
Nothing
{-# INLINE noGLint64 #-}
type GLsizei = Int32
noGLsizei :: Maybe GLsizei
noGLsizei :: Maybe GLint
noGLsizei = Maybe GLint
forall a. Maybe a
Nothing
{-# INLINE noGLsizei #-}
type GLintptr = Int64
noGLintptr :: Maybe GLintptr
noGLintptr :: Maybe GLint64
noGLintptr = Maybe GLint64
forall a. Maybe a
Nothing
{-# INLINE noGLintptr #-}
type GLsizeiptr = Int64
noGLsizeiptr :: Maybe GLsizeiptr
noGLsizeiptr :: Maybe GLint64
noGLsizeiptr = Maybe GLint64
forall a. Maybe a
Nothing
{-# INLINE noGLsizeiptr #-}
type GLubyte = Word8
noGLubyte :: Maybe GLubyte
noGLubyte :: Maybe GLubyte
noGLubyte = Maybe GLubyte
forall a. Maybe a
Nothing
{-# INLINE noGLubyte #-}
type GLushort = Word16
noGLushort :: Maybe GLushort
noGLushort :: Maybe GLushort
noGLushort = Maybe GLushort
forall a. Maybe a
Nothing
{-# INLINE noGLushort #-}
type GLuint = Word32
noGLuint :: Maybe GLuint
noGLuint :: Maybe GLenum
noGLuint = Maybe GLenum
forall a. Maybe a
Nothing
{-# INLINE noGLuint #-}
type GLuint64 = Word64
noGLuint64 :: Maybe GLuint64
noGLuint64 :: Maybe GLuint64
noGLuint64 = Maybe GLuint64
forall a. Maybe a
Nothing
{-# INLINE noGLuint64 #-}
type GLfloat = Double
noGLfloat :: Maybe GLfloat
noGLfloat :: Maybe Double
noGLfloat = Maybe Double
forall a. Maybe a
Nothing
{-# INLINE noGLfloat #-}
type GLclampf = Double
noGLclampf :: Maybe GLclampf
noGLclampf :: Maybe Double
noGLclampf = Maybe Double
forall a. Maybe a
Nothing
{-# INLINE noGLclampf #-}

-- This type is used to access the `globalThis` (see https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Global_Objects/globalThis)
newtype GlobalThis = GlobalThis { GlobalThis -> JSVal
unGlobalThis :: JSVal }

instance PToJSVal GlobalThis where
  pToJSVal :: GlobalThis -> JSVal
pToJSVal = GlobalThis -> JSVal
unGlobalThis
  {-# INLINE pToJSVal #-}

instance PFromJSVal GlobalThis where
  pFromJSVal :: JSVal -> GlobalThis
pFromJSVal = JSVal -> GlobalThis
GlobalThis
  {-# INLINE pFromJSVal #-}

instance ToJSVal GlobalThis where
  toJSVal :: GlobalThis -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (GlobalThis -> JSVal) -> GlobalThis -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalThis -> JSVal
unGlobalThis
  {-# INLINE toJSVal #-}

instance FromJSVal GlobalThis where
  fromJSVal :: JSVal -> JSM (Maybe GlobalThis)
fromJSVal JSVal
v = (JSVal -> GlobalThis) -> Maybe JSVal -> Maybe GlobalThis
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> GlobalThis
GlobalThis (Maybe JSVal -> Maybe GlobalThis)
-> JSM (Maybe JSVal) -> JSM (Maybe GlobalThis)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM GlobalThis
fromJSValUnchecked = GlobalThis -> JSM GlobalThis
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (GlobalThis -> JSM GlobalThis)
-> (JSVal -> GlobalThis) -> JSVal -> JSM GlobalThis
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> GlobalThis
GlobalThis
  {-# INLINE fromJSValUnchecked #-}

instance IsGObject GlobalThis where
  typeGType :: GlobalThis -> JSM GType
typeGType GlobalThis
_ = String -> JSM GType
forall a. HasCallStack => String -> a
error String
"Unable to get the JavaScript type of GlobalThis"

instance MakeObject GlobalThis where
  makeObject :: GlobalThis -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (GlobalThis -> JSVal) -> GlobalThis -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalThis -> JSVal
unGlobalThis

instance IsEventTarget GlobalThis
instance IsWindowOrWorkerGlobalScope GlobalThis
instance IsGlobalPerformance GlobalThis
instance IsGlobalEventHandlers GlobalThis
instance IsGlobalCrypto GlobalThis
noGlobalThis :: Maybe GlobalThis
noGlobalThis :: Maybe GlobalThis
noGlobalThis = Maybe GlobalThis
forall a. Maybe a
Nothing
{-# INLINE noGlobalThis #-}

-- AUTO GENERATION STARTS HERE
-- The remainder of this file is generated from IDL files using domconv-webkit-jsffi
newtype AddEventListenerOptionsOrBool = AddEventListenerOptionsOrBool { AddEventListenerOptionsOrBool -> JSVal
unAddEventListenerOptionsOrBool :: JSVal }

instance PToJSVal AddEventListenerOptionsOrBool where
  pToJSVal :: AddEventListenerOptionsOrBool -> JSVal
pToJSVal = AddEventListenerOptionsOrBool -> JSVal
unAddEventListenerOptionsOrBool
  {-# INLINE pToJSVal #-}

instance PFromJSVal AddEventListenerOptionsOrBool where
  pFromJSVal :: JSVal -> AddEventListenerOptionsOrBool
pFromJSVal = JSVal -> AddEventListenerOptionsOrBool
AddEventListenerOptionsOrBool
  {-# INLINE pFromJSVal #-}

instance ToJSVal AddEventListenerOptionsOrBool where
  toJSVal :: AddEventListenerOptionsOrBool -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AddEventListenerOptionsOrBool -> JSVal)
-> AddEventListenerOptionsOrBool
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AddEventListenerOptionsOrBool -> JSVal
unAddEventListenerOptionsOrBool
  {-# INLINE toJSVal #-}

instance FromJSVal AddEventListenerOptionsOrBool where
  fromJSVal :: JSVal -> JSM (Maybe AddEventListenerOptionsOrBool)
fromJSVal JSVal
v = (JSVal -> AddEventListenerOptionsOrBool)
-> Maybe JSVal -> Maybe AddEventListenerOptionsOrBool
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AddEventListenerOptionsOrBool
AddEventListenerOptionsOrBool (Maybe JSVal -> Maybe AddEventListenerOptionsOrBool)
-> JSM (Maybe JSVal) -> JSM (Maybe AddEventListenerOptionsOrBool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AddEventListenerOptionsOrBool
fromJSValUnchecked = AddEventListenerOptionsOrBool -> JSM AddEventListenerOptionsOrBool
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AddEventListenerOptionsOrBool
 -> JSM AddEventListenerOptionsOrBool)
-> (JSVal -> AddEventListenerOptionsOrBool)
-> JSVal
-> JSM AddEventListenerOptionsOrBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AddEventListenerOptionsOrBool
AddEventListenerOptionsOrBool
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AddEventListenerOptionsOrBool where
  makeObject :: AddEventListenerOptionsOrBool -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AddEventListenerOptionsOrBool -> JSVal)
-> AddEventListenerOptionsOrBool
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AddEventListenerOptionsOrBool -> JSVal
unAddEventListenerOptionsOrBool

class (FromJSVal o, ToJSVal o, PToJSVal o) => IsAddEventListenerOptionsOrBool o

toAddEventListenerOptionsOrBool :: IsAddEventListenerOptionsOrBool o => o -> AddEventListenerOptionsOrBool
toAddEventListenerOptionsOrBool :: forall o.
IsAddEventListenerOptionsOrBool o =>
o -> AddEventListenerOptionsOrBool
toAddEventListenerOptionsOrBool = JSVal -> AddEventListenerOptionsOrBool
AddEventListenerOptionsOrBool (JSVal -> AddEventListenerOptionsOrBool)
-> (o -> JSVal) -> o -> AddEventListenerOptionsOrBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a. PToJSVal a => a -> JSVal
pToJSVal

instance IsAddEventListenerOptionsOrBool AddEventListenerOptionsOrBool
instance IsAddEventListenerOptionsOrBool Bool
instance IsAddEventListenerOptionsOrBool AddEventListenerOptions

newtype BinaryData = BinaryData { BinaryData -> JSVal
unBinaryData :: JSVal }

instance PToJSVal BinaryData where
  pToJSVal :: BinaryData -> JSVal
pToJSVal = BinaryData -> JSVal
unBinaryData
  {-# INLINE pToJSVal #-}

instance PFromJSVal BinaryData where
  pFromJSVal :: JSVal -> BinaryData
pFromJSVal = JSVal -> BinaryData
BinaryData
  {-# INLINE pFromJSVal #-}

instance ToJSVal BinaryData where
  toJSVal :: BinaryData -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (BinaryData -> JSVal) -> BinaryData -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BinaryData -> JSVal
unBinaryData
  {-# INLINE toJSVal #-}

instance FromJSVal BinaryData where
  fromJSVal :: JSVal -> JSM (Maybe BinaryData)
fromJSVal JSVal
v = (JSVal -> BinaryData) -> Maybe JSVal -> Maybe BinaryData
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BinaryData
BinaryData (Maybe JSVal -> Maybe BinaryData)
-> JSM (Maybe JSVal) -> JSM (Maybe BinaryData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BinaryData
fromJSValUnchecked = BinaryData -> JSM BinaryData
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BinaryData -> JSM BinaryData)
-> (JSVal -> BinaryData) -> JSVal -> JSM BinaryData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BinaryData
BinaryData
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BinaryData where
  makeObject :: BinaryData -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BinaryData -> JSVal) -> BinaryData -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BinaryData -> JSVal
unBinaryData

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBinaryData o

toBinaryData :: IsBinaryData o => o -> BinaryData
toBinaryData :: forall o. IsBinaryData o => o -> BinaryData
toBinaryData = JSVal -> BinaryData
BinaryData (JSVal -> BinaryData) -> (o -> JSVal) -> o -> BinaryData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsBinaryData BinaryData
instance IsBinaryData ArrayBuffer
instance IsBinaryData ArrayBufferView

newtype BlobPart = BlobPart { BlobPart -> JSVal
unBlobPart :: JSVal }

instance PToJSVal BlobPart where
  pToJSVal :: BlobPart -> JSVal
pToJSVal = BlobPart -> JSVal
unBlobPart
  {-# INLINE pToJSVal #-}

instance PFromJSVal BlobPart where
  pFromJSVal :: JSVal -> BlobPart
pFromJSVal = JSVal -> BlobPart
BlobPart
  {-# INLINE pFromJSVal #-}

instance ToJSVal BlobPart where
  toJSVal :: BlobPart -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (BlobPart -> JSVal) -> BlobPart -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlobPart -> JSVal
unBlobPart
  {-# INLINE toJSVal #-}

instance FromJSVal BlobPart where
  fromJSVal :: JSVal -> JSM (Maybe BlobPart)
fromJSVal JSVal
v = (JSVal -> BlobPart) -> Maybe JSVal -> Maybe BlobPart
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BlobPart
BlobPart (Maybe JSVal -> Maybe BlobPart)
-> JSM (Maybe JSVal) -> JSM (Maybe BlobPart)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BlobPart
fromJSValUnchecked = BlobPart -> JSM BlobPart
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BlobPart -> JSM BlobPart)
-> (JSVal -> BlobPart) -> JSVal -> JSM BlobPart
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BlobPart
BlobPart
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BlobPart where
  makeObject :: BlobPart -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BlobPart -> JSVal) -> BlobPart -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlobPart -> JSVal
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 { BodyInit -> JSVal
unBodyInit :: JSVal }

instance PToJSVal BodyInit where
  pToJSVal :: BodyInit -> JSVal
pToJSVal = BodyInit -> JSVal
unBodyInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal BodyInit where
  pFromJSVal :: JSVal -> BodyInit
pFromJSVal = JSVal -> BodyInit
BodyInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal BodyInit where
  toJSVal :: BodyInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (BodyInit -> JSVal) -> BodyInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BodyInit -> JSVal
unBodyInit
  {-# INLINE toJSVal #-}

instance FromJSVal BodyInit where
  fromJSVal :: JSVal -> JSM (Maybe BodyInit)
fromJSVal JSVal
v = (JSVal -> BodyInit) -> Maybe JSVal -> Maybe BodyInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BodyInit
BodyInit (Maybe JSVal -> Maybe BodyInit)
-> JSM (Maybe JSVal) -> JSM (Maybe BodyInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BodyInit
fromJSValUnchecked = BodyInit -> JSM BodyInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BodyInit -> JSM BodyInit)
-> (JSVal -> BodyInit) -> JSVal -> JSM BodyInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BodyInit
BodyInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BodyInit where
  makeObject :: BodyInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BodyInit -> JSVal) -> BodyInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BodyInit -> JSVal
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 { BufferDataSource -> JSVal
unBufferDataSource :: JSVal }

instance PToJSVal BufferDataSource where
  pToJSVal :: BufferDataSource -> JSVal
pToJSVal = BufferDataSource -> JSVal
unBufferDataSource
  {-# INLINE pToJSVal #-}

instance PFromJSVal BufferDataSource where
  pFromJSVal :: JSVal -> BufferDataSource
pFromJSVal = JSVal -> BufferDataSource
BufferDataSource
  {-# INLINE pFromJSVal #-}

instance ToJSVal BufferDataSource where
  toJSVal :: BufferDataSource -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (BufferDataSource -> JSVal) -> BufferDataSource -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BufferDataSource -> JSVal
unBufferDataSource
  {-# INLINE toJSVal #-}

instance FromJSVal BufferDataSource where
  fromJSVal :: JSVal -> JSM (Maybe BufferDataSource)
fromJSVal JSVal
v = (JSVal -> BufferDataSource)
-> Maybe JSVal -> Maybe BufferDataSource
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BufferDataSource
BufferDataSource (Maybe JSVal -> Maybe BufferDataSource)
-> JSM (Maybe JSVal) -> JSM (Maybe BufferDataSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BufferDataSource
fromJSValUnchecked = BufferDataSource -> JSM BufferDataSource
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BufferDataSource -> JSM BufferDataSource)
-> (JSVal -> BufferDataSource) -> JSVal -> JSM BufferDataSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BufferDataSource
BufferDataSource
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BufferDataSource where
  makeObject :: BufferDataSource -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BufferDataSource -> JSVal) -> BufferDataSource -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BufferDataSource -> JSVal
unBufferDataSource

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBufferDataSource o

toBufferDataSource :: IsBufferDataSource o => o -> BufferDataSource
toBufferDataSource :: forall o. IsBufferDataSource o => o -> BufferDataSource
toBufferDataSource = JSVal -> BufferDataSource
BufferDataSource (JSVal -> BufferDataSource)
-> (o -> JSVal) -> o -> BufferDataSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsBufferDataSource BufferDataSource
instance IsBufferDataSource ArrayBuffer
instance IsBufferDataSource ArrayBufferView

newtype BufferSource = BufferSource { BufferSource -> JSVal
unBufferSource :: JSVal }

instance PToJSVal BufferSource where
  pToJSVal :: BufferSource -> JSVal
pToJSVal = BufferSource -> JSVal
unBufferSource
  {-# INLINE pToJSVal #-}

instance PFromJSVal BufferSource where
  pFromJSVal :: JSVal -> BufferSource
pFromJSVal = JSVal -> BufferSource
BufferSource
  {-# INLINE pFromJSVal #-}

instance ToJSVal BufferSource where
  toJSVal :: BufferSource -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (BufferSource -> JSVal) -> BufferSource -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BufferSource -> JSVal
unBufferSource
  {-# INLINE toJSVal #-}

instance FromJSVal BufferSource where
  fromJSVal :: JSVal -> JSM (Maybe BufferSource)
fromJSVal JSVal
v = (JSVal -> BufferSource) -> Maybe JSVal -> Maybe BufferSource
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BufferSource
BufferSource (Maybe JSVal -> Maybe BufferSource)
-> JSM (Maybe JSVal) -> JSM (Maybe BufferSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BufferSource
fromJSValUnchecked = BufferSource -> JSM BufferSource
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BufferSource -> JSM BufferSource)
-> (JSVal -> BufferSource) -> JSVal -> JSM BufferSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BufferSource
BufferSource
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BufferSource where
  makeObject :: BufferSource -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BufferSource -> JSVal) -> BufferSource -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BufferSource -> JSVal
unBufferSource

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsBufferSource o

toBufferSource :: IsBufferSource o => o -> BufferSource
toBufferSource :: forall o. IsBufferSource o => o -> BufferSource
toBufferSource = JSVal -> BufferSource
BufferSource (JSVal -> BufferSource) -> (o -> JSVal) -> o -> BufferSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsBufferSource BufferSource
instance IsBufferSource ArrayBuffer
instance IsBufferSource ArrayBufferView

newtype CanvasImageSource = CanvasImageSource { CanvasImageSource -> JSVal
unCanvasImageSource :: JSVal }

instance PToJSVal CanvasImageSource where
  pToJSVal :: CanvasImageSource -> JSVal
pToJSVal = CanvasImageSource -> JSVal
unCanvasImageSource
  {-# INLINE pToJSVal #-}

instance PFromJSVal CanvasImageSource where
  pFromJSVal :: JSVal -> CanvasImageSource
pFromJSVal = JSVal -> CanvasImageSource
CanvasImageSource
  {-# INLINE pFromJSVal #-}

instance ToJSVal CanvasImageSource where
  toJSVal :: CanvasImageSource -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CanvasImageSource -> JSVal) -> CanvasImageSource -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasImageSource -> JSVal
unCanvasImageSource
  {-# INLINE toJSVal #-}

instance FromJSVal CanvasImageSource where
  fromJSVal :: JSVal -> JSM (Maybe CanvasImageSource)
fromJSVal JSVal
v = (JSVal -> CanvasImageSource)
-> Maybe JSVal -> Maybe CanvasImageSource
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CanvasImageSource
CanvasImageSource (Maybe JSVal -> Maybe CanvasImageSource)
-> JSM (Maybe JSVal) -> JSM (Maybe CanvasImageSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CanvasImageSource
fromJSValUnchecked = CanvasImageSource -> JSM CanvasImageSource
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CanvasImageSource -> JSM CanvasImageSource)
-> (JSVal -> CanvasImageSource) -> JSVal -> JSM CanvasImageSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CanvasImageSource
CanvasImageSource
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CanvasImageSource where
  makeObject :: CanvasImageSource -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CanvasImageSource -> JSVal) -> CanvasImageSource -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasImageSource -> JSVal
unCanvasImageSource

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCanvasImageSource o

toCanvasImageSource :: IsCanvasImageSource o => o -> CanvasImageSource
toCanvasImageSource :: forall o. IsCanvasImageSource o => o -> CanvasImageSource
toCanvasImageSource = JSVal -> CanvasImageSource
CanvasImageSource (JSVal -> CanvasImageSource)
-> (o -> JSVal) -> o -> CanvasImageSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsCanvasImageSource CanvasImageSource
instance IsCanvasImageSource HTMLImageElement
instance IsCanvasImageSource HTMLVideoElement
instance IsCanvasImageSource HTMLCanvasElement

newtype CanvasStyle = CanvasStyle { CanvasStyle -> JSVal
unCanvasStyle :: JSVal }

instance PToJSVal CanvasStyle where
  pToJSVal :: CanvasStyle -> JSVal
pToJSVal = CanvasStyle -> JSVal
unCanvasStyle
  {-# INLINE pToJSVal #-}

instance PFromJSVal CanvasStyle where
  pFromJSVal :: JSVal -> CanvasStyle
pFromJSVal = JSVal -> CanvasStyle
CanvasStyle
  {-# INLINE pFromJSVal #-}

instance ToJSVal CanvasStyle where
  toJSVal :: CanvasStyle -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CanvasStyle -> JSVal) -> CanvasStyle -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasStyle -> JSVal
unCanvasStyle
  {-# INLINE toJSVal #-}

instance FromJSVal CanvasStyle where
  fromJSVal :: JSVal -> JSM (Maybe CanvasStyle)
fromJSVal JSVal
v = (JSVal -> CanvasStyle) -> Maybe JSVal -> Maybe CanvasStyle
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CanvasStyle
CanvasStyle (Maybe JSVal -> Maybe CanvasStyle)
-> JSM (Maybe JSVal) -> JSM (Maybe CanvasStyle)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CanvasStyle
fromJSValUnchecked = CanvasStyle -> JSM CanvasStyle
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CanvasStyle -> JSM CanvasStyle)
-> (JSVal -> CanvasStyle) -> JSVal -> JSM CanvasStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CanvasStyle
CanvasStyle
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CanvasStyle where
  makeObject :: CanvasStyle -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CanvasStyle -> JSVal) -> CanvasStyle -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasStyle -> JSVal
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 { CredentialBodyType -> JSVal
unCredentialBodyType :: JSVal }

instance PToJSVal CredentialBodyType where
  pToJSVal :: CredentialBodyType -> JSVal
pToJSVal = CredentialBodyType -> JSVal
unCredentialBodyType
  {-# INLINE pToJSVal #-}

instance PFromJSVal CredentialBodyType where
  pFromJSVal :: JSVal -> CredentialBodyType
pFromJSVal = JSVal -> CredentialBodyType
CredentialBodyType
  {-# INLINE pFromJSVal #-}

instance ToJSVal CredentialBodyType where
  toJSVal :: CredentialBodyType -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CredentialBodyType -> JSVal) -> CredentialBodyType -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CredentialBodyType -> JSVal
unCredentialBodyType
  {-# INLINE toJSVal #-}

instance FromJSVal CredentialBodyType where
  fromJSVal :: JSVal -> JSM (Maybe CredentialBodyType)
fromJSVal JSVal
v = (JSVal -> CredentialBodyType)
-> Maybe JSVal -> Maybe CredentialBodyType
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CredentialBodyType
CredentialBodyType (Maybe JSVal -> Maybe CredentialBodyType)
-> JSM (Maybe JSVal) -> JSM (Maybe CredentialBodyType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CredentialBodyType
fromJSValUnchecked = CredentialBodyType -> JSM CredentialBodyType
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CredentialBodyType -> JSM CredentialBodyType)
-> (JSVal -> CredentialBodyType) -> JSVal -> JSM CredentialBodyType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CredentialBodyType
CredentialBodyType
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CredentialBodyType where
  makeObject :: CredentialBodyType -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CredentialBodyType -> JSVal)
-> CredentialBodyType
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CredentialBodyType -> JSVal
unCredentialBodyType

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCredentialBodyType o

toCredentialBodyType :: IsCredentialBodyType o => o -> CredentialBodyType
toCredentialBodyType :: forall o. IsCredentialBodyType o => o -> CredentialBodyType
toCredentialBodyType = JSVal -> CredentialBodyType
CredentialBodyType (JSVal -> CredentialBodyType)
-> (o -> JSVal) -> o -> CredentialBodyType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsCredentialBodyType CredentialBodyType
instance IsCredentialBodyType URLSearchParams
instance IsCredentialBodyType FormData

newtype CryptoKeyOrKeyPair = CryptoKeyOrKeyPair { CryptoKeyOrKeyPair -> JSVal
unCryptoKeyOrKeyPair :: JSVal }

instance PToJSVal CryptoKeyOrKeyPair where
  pToJSVal :: CryptoKeyOrKeyPair -> JSVal
pToJSVal = CryptoKeyOrKeyPair -> JSVal
unCryptoKeyOrKeyPair
  {-# INLINE pToJSVal #-}

instance PFromJSVal CryptoKeyOrKeyPair where
  pFromJSVal :: JSVal -> CryptoKeyOrKeyPair
pFromJSVal = JSVal -> CryptoKeyOrKeyPair
CryptoKeyOrKeyPair
  {-# INLINE pFromJSVal #-}

instance ToJSVal CryptoKeyOrKeyPair where
  toJSVal :: CryptoKeyOrKeyPair -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CryptoKeyOrKeyPair -> JSVal) -> CryptoKeyOrKeyPair -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CryptoKeyOrKeyPair -> JSVal
unCryptoKeyOrKeyPair
  {-# INLINE toJSVal #-}

instance FromJSVal CryptoKeyOrKeyPair where
  fromJSVal :: JSVal -> JSM (Maybe CryptoKeyOrKeyPair)
fromJSVal JSVal
v = (JSVal -> CryptoKeyOrKeyPair)
-> Maybe JSVal -> Maybe CryptoKeyOrKeyPair
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CryptoKeyOrKeyPair
CryptoKeyOrKeyPair (Maybe JSVal -> Maybe CryptoKeyOrKeyPair)
-> JSM (Maybe JSVal) -> JSM (Maybe CryptoKeyOrKeyPair)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CryptoKeyOrKeyPair
fromJSValUnchecked = CryptoKeyOrKeyPair -> JSM CryptoKeyOrKeyPair
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CryptoKeyOrKeyPair -> JSM CryptoKeyOrKeyPair)
-> (JSVal -> CryptoKeyOrKeyPair) -> JSVal -> JSM CryptoKeyOrKeyPair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CryptoKeyOrKeyPair
CryptoKeyOrKeyPair
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CryptoKeyOrKeyPair where
  makeObject :: CryptoKeyOrKeyPair -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CryptoKeyOrKeyPair -> JSVal)
-> CryptoKeyOrKeyPair
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CryptoKeyOrKeyPair -> JSVal
unCryptoKeyOrKeyPair

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsCryptoKeyOrKeyPair o

toCryptoKeyOrKeyPair :: IsCryptoKeyOrKeyPair o => o -> CryptoKeyOrKeyPair
toCryptoKeyOrKeyPair :: forall o. IsCryptoKeyOrKeyPair o => o -> CryptoKeyOrKeyPair
toCryptoKeyOrKeyPair = JSVal -> CryptoKeyOrKeyPair
CryptoKeyOrKeyPair (JSVal -> CryptoKeyOrKeyPair)
-> (o -> JSVal) -> o -> CryptoKeyOrKeyPair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsCryptoKeyOrKeyPair CryptoKeyOrKeyPair
instance IsCryptoKeyOrKeyPair CryptoKeyPair
instance IsCryptoKeyOrKeyPair CryptoKey

newtype EventListenerOptionsOrBool = EventListenerOptionsOrBool { EventListenerOptionsOrBool -> JSVal
unEventListenerOptionsOrBool :: JSVal }

instance PToJSVal EventListenerOptionsOrBool where
  pToJSVal :: EventListenerOptionsOrBool -> JSVal
pToJSVal = EventListenerOptionsOrBool -> JSVal
unEventListenerOptionsOrBool
  {-# INLINE pToJSVal #-}

instance PFromJSVal EventListenerOptionsOrBool where
  pFromJSVal :: JSVal -> EventListenerOptionsOrBool
pFromJSVal = JSVal -> EventListenerOptionsOrBool
EventListenerOptionsOrBool
  {-# INLINE pFromJSVal #-}

instance ToJSVal EventListenerOptionsOrBool where
  toJSVal :: EventListenerOptionsOrBool -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EventListenerOptionsOrBool -> JSVal)
-> EventListenerOptionsOrBool
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventListenerOptionsOrBool -> JSVal
unEventListenerOptionsOrBool
  {-# INLINE toJSVal #-}

instance FromJSVal EventListenerOptionsOrBool where
  fromJSVal :: JSVal -> JSM (Maybe EventListenerOptionsOrBool)
fromJSVal JSVal
v = (JSVal -> EventListenerOptionsOrBool)
-> Maybe JSVal -> Maybe EventListenerOptionsOrBool
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EventListenerOptionsOrBool
EventListenerOptionsOrBool (Maybe JSVal -> Maybe EventListenerOptionsOrBool)
-> JSM (Maybe JSVal) -> JSM (Maybe EventListenerOptionsOrBool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EventListenerOptionsOrBool
fromJSValUnchecked = EventListenerOptionsOrBool -> JSM EventListenerOptionsOrBool
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EventListenerOptionsOrBool -> JSM EventListenerOptionsOrBool)
-> (JSVal -> EventListenerOptionsOrBool)
-> JSVal
-> JSM EventListenerOptionsOrBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EventListenerOptionsOrBool
EventListenerOptionsOrBool
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EventListenerOptionsOrBool where
  makeObject :: EventListenerOptionsOrBool -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EventListenerOptionsOrBool -> JSVal)
-> EventListenerOptionsOrBool
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventListenerOptionsOrBool -> JSVal
unEventListenerOptionsOrBool

class (FromJSVal o, ToJSVal o, PToJSVal o) => IsEventListenerOptionsOrBool o

toEventListenerOptionsOrBool :: IsEventListenerOptionsOrBool o => o -> EventListenerOptionsOrBool
toEventListenerOptionsOrBool :: forall o.
IsEventListenerOptionsOrBool o =>
o -> EventListenerOptionsOrBool
toEventListenerOptionsOrBool = JSVal -> EventListenerOptionsOrBool
EventListenerOptionsOrBool (JSVal -> EventListenerOptionsOrBool)
-> (o -> JSVal) -> o -> EventListenerOptionsOrBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a. PToJSVal a => a -> JSVal
pToJSVal

instance IsEventListenerOptionsOrBool EventListenerOptionsOrBool
instance IsEventListenerOptionsOrBool Bool
instance IsEventListenerOptionsOrBool EventListenerOptions
instance IsEventListenerOptionsOrBool AddEventListenerOptions

newtype Float32List = Float32List { Float32List -> JSVal
unFloat32List :: JSVal }

instance PToJSVal Float32List where
  pToJSVal :: Float32List -> JSVal
pToJSVal = Float32List -> JSVal
unFloat32List
  {-# INLINE pToJSVal #-}

instance PFromJSVal Float32List where
  pFromJSVal :: JSVal -> Float32List
pFromJSVal = JSVal -> Float32List
Float32List
  {-# INLINE pFromJSVal #-}

instance ToJSVal Float32List where
  toJSVal :: Float32List -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Float32List -> JSVal) -> Float32List -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float32List -> JSVal
unFloat32List
  {-# INLINE toJSVal #-}

instance FromJSVal Float32List where
  fromJSVal :: JSVal -> JSM (Maybe Float32List)
fromJSVal JSVal
v = (JSVal -> Float32List) -> Maybe JSVal -> Maybe Float32List
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Float32List
Float32List (Maybe JSVal -> Maybe Float32List)
-> JSM (Maybe JSVal) -> JSM (Maybe Float32List)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Float32List
fromJSValUnchecked = Float32List -> JSM Float32List
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Float32List -> JSM Float32List)
-> (JSVal -> Float32List) -> JSVal -> JSM Float32List
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Float32List
Float32List
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Float32List where
  makeObject :: Float32List -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Float32List -> JSVal) -> Float32List -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float32List -> JSVal
unFloat32List

class (FromJSVal o, ToJSVal o) => IsFloat32List o

instance IsFloat32List Float32List
instance IsFloat32List [GLfloat]
instance IsFloat32List Float32Array

newtype HTMLCollectionOrElement = HTMLCollectionOrElement { HTMLCollectionOrElement -> JSVal
unHTMLCollectionOrElement :: JSVal }

instance PToJSVal HTMLCollectionOrElement where
  pToJSVal :: HTMLCollectionOrElement -> JSVal
pToJSVal = HTMLCollectionOrElement -> JSVal
unHTMLCollectionOrElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLCollectionOrElement where
  pFromJSVal :: JSVal -> HTMLCollectionOrElement
pFromJSVal = JSVal -> HTMLCollectionOrElement
HTMLCollectionOrElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLCollectionOrElement where
  toJSVal :: HTMLCollectionOrElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLCollectionOrElement -> JSVal)
-> HTMLCollectionOrElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLCollectionOrElement -> JSVal
unHTMLCollectionOrElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLCollectionOrElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLCollectionOrElement)
fromJSVal JSVal
v = (JSVal -> HTMLCollectionOrElement)
-> Maybe JSVal -> Maybe HTMLCollectionOrElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLCollectionOrElement
HTMLCollectionOrElement (Maybe JSVal -> Maybe HTMLCollectionOrElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLCollectionOrElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLCollectionOrElement
fromJSValUnchecked = HTMLCollectionOrElement -> JSM HTMLCollectionOrElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLCollectionOrElement -> JSM HTMLCollectionOrElement)
-> (JSVal -> HTMLCollectionOrElement)
-> JSVal
-> JSM HTMLCollectionOrElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLCollectionOrElement
HTMLCollectionOrElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLCollectionOrElement where
  makeObject :: HTMLCollectionOrElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLCollectionOrElement -> JSVal)
-> HTMLCollectionOrElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLCollectionOrElement -> JSVal
unHTMLCollectionOrElement

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsHTMLCollectionOrElement o

toHTMLCollectionOrElement :: IsHTMLCollectionOrElement o => o -> HTMLCollectionOrElement
toHTMLCollectionOrElement :: forall o.
IsHTMLCollectionOrElement o =>
o -> HTMLCollectionOrElement
toHTMLCollectionOrElement = JSVal -> HTMLCollectionOrElement
HTMLCollectionOrElement (JSVal -> HTMLCollectionOrElement)
-> (o -> JSVal) -> o -> HTMLCollectionOrElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 { HTMLElementOrLong -> JSVal
unHTMLElementOrLong :: JSVal }

instance PToJSVal HTMLElementOrLong where
  pToJSVal :: HTMLElementOrLong -> JSVal
pToJSVal = HTMLElementOrLong -> JSVal
unHTMLElementOrLong
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLElementOrLong where
  pFromJSVal :: JSVal -> HTMLElementOrLong
pFromJSVal = JSVal -> HTMLElementOrLong
HTMLElementOrLong
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLElementOrLong where
  toJSVal :: HTMLElementOrLong -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLElementOrLong -> JSVal) -> HTMLElementOrLong -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLElementOrLong -> JSVal
unHTMLElementOrLong
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLElementOrLong where
  fromJSVal :: JSVal -> JSM (Maybe HTMLElementOrLong)
fromJSVal JSVal
v = (JSVal -> HTMLElementOrLong)
-> Maybe JSVal -> Maybe HTMLElementOrLong
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLElementOrLong
HTMLElementOrLong (Maybe JSVal -> Maybe HTMLElementOrLong)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLElementOrLong)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLElementOrLong
fromJSValUnchecked = HTMLElementOrLong -> JSM HTMLElementOrLong
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLElementOrLong -> JSM HTMLElementOrLong)
-> (JSVal -> HTMLElementOrLong) -> JSVal -> JSM HTMLElementOrLong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLElementOrLong
HTMLElementOrLong
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLElementOrLong where
  makeObject :: HTMLElementOrLong -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLElementOrLong -> JSVal) -> HTMLElementOrLong -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLElementOrLong -> JSVal
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 { HTMLOptionElementOrGroup -> JSVal
unHTMLOptionElementOrGroup :: JSVal }

instance PToJSVal HTMLOptionElementOrGroup where
  pToJSVal :: HTMLOptionElementOrGroup -> JSVal
pToJSVal = HTMLOptionElementOrGroup -> JSVal
unHTMLOptionElementOrGroup
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLOptionElementOrGroup where
  pFromJSVal :: JSVal -> HTMLOptionElementOrGroup
pFromJSVal = JSVal -> HTMLOptionElementOrGroup
HTMLOptionElementOrGroup
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLOptionElementOrGroup where
  toJSVal :: HTMLOptionElementOrGroup -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLOptionElementOrGroup -> JSVal)
-> HTMLOptionElementOrGroup
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOptionElementOrGroup -> JSVal
unHTMLOptionElementOrGroup
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLOptionElementOrGroup where
  fromJSVal :: JSVal -> JSM (Maybe HTMLOptionElementOrGroup)
fromJSVal JSVal
v = (JSVal -> HTMLOptionElementOrGroup)
-> Maybe JSVal -> Maybe HTMLOptionElementOrGroup
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLOptionElementOrGroup
HTMLOptionElementOrGroup (Maybe JSVal -> Maybe HTMLOptionElementOrGroup)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLOptionElementOrGroup)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLOptionElementOrGroup
fromJSValUnchecked = HTMLOptionElementOrGroup -> JSM HTMLOptionElementOrGroup
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLOptionElementOrGroup -> JSM HTMLOptionElementOrGroup)
-> (JSVal -> HTMLOptionElementOrGroup)
-> JSVal
-> JSM HTMLOptionElementOrGroup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLOptionElementOrGroup
HTMLOptionElementOrGroup
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLOptionElementOrGroup where
  makeObject :: HTMLOptionElementOrGroup -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLOptionElementOrGroup -> JSVal)
-> HTMLOptionElementOrGroup
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOptionElementOrGroup -> JSVal
unHTMLOptionElementOrGroup

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsHTMLOptionElementOrGroup o

toHTMLOptionElementOrGroup :: IsHTMLOptionElementOrGroup o => o -> HTMLOptionElementOrGroup
toHTMLOptionElementOrGroup :: forall o.
IsHTMLOptionElementOrGroup o =>
o -> HTMLOptionElementOrGroup
toHTMLOptionElementOrGroup = JSVal -> HTMLOptionElementOrGroup
HTMLOptionElementOrGroup (JSVal -> HTMLOptionElementOrGroup)
-> (o -> JSVal) -> o -> HTMLOptionElementOrGroup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsHTMLOptionElementOrGroup HTMLOptionElementOrGroup
instance IsHTMLOptionElementOrGroup HTMLOptGroupElement
instance IsHTMLOptionElementOrGroup HTMLOptionElement

newtype IDBCursorSource = IDBCursorSource { IDBCursorSource -> JSVal
unIDBCursorSource :: JSVal }

instance PToJSVal IDBCursorSource where
  pToJSVal :: IDBCursorSource -> JSVal
pToJSVal = IDBCursorSource -> JSVal
unIDBCursorSource
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBCursorSource where
  pFromJSVal :: JSVal -> IDBCursorSource
pFromJSVal = JSVal -> IDBCursorSource
IDBCursorSource
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBCursorSource where
  toJSVal :: IDBCursorSource -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBCursorSource -> JSVal) -> IDBCursorSource -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBCursorSource -> JSVal
unIDBCursorSource
  {-# INLINE toJSVal #-}

instance FromJSVal IDBCursorSource where
  fromJSVal :: JSVal -> JSM (Maybe IDBCursorSource)
fromJSVal JSVal
v = (JSVal -> IDBCursorSource) -> Maybe JSVal -> Maybe IDBCursorSource
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBCursorSource
IDBCursorSource (Maybe JSVal -> Maybe IDBCursorSource)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBCursorSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBCursorSource
fromJSValUnchecked = IDBCursorSource -> JSM IDBCursorSource
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBCursorSource -> JSM IDBCursorSource)
-> (JSVal -> IDBCursorSource) -> JSVal -> JSM IDBCursorSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBCursorSource
IDBCursorSource
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBCursorSource where
  makeObject :: IDBCursorSource -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBCursorSource -> JSVal) -> IDBCursorSource -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBCursorSource -> JSVal
unIDBCursorSource

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBCursorSource o

toIDBCursorSource :: IsIDBCursorSource o => o -> IDBCursorSource
toIDBCursorSource :: forall o. IsIDBCursorSource o => o -> IDBCursorSource
toIDBCursorSource = JSVal -> IDBCursorSource
IDBCursorSource (JSVal -> IDBCursorSource) -> (o -> JSVal) -> o -> IDBCursorSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsIDBCursorSource IDBCursorSource
instance IsIDBCursorSource IDBIndex
instance IsIDBCursorSource IDBObjectStore

newtype IDBKeyPath = IDBKeyPath { IDBKeyPath -> JSVal
unIDBKeyPath :: JSVal }

instance PToJSVal IDBKeyPath where
  pToJSVal :: IDBKeyPath -> JSVal
pToJSVal = IDBKeyPath -> JSVal
unIDBKeyPath
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBKeyPath where
  pFromJSVal :: JSVal -> IDBKeyPath
pFromJSVal = JSVal -> IDBKeyPath
IDBKeyPath
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBKeyPath where
  toJSVal :: IDBKeyPath -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBKeyPath -> JSVal) -> IDBKeyPath -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBKeyPath -> JSVal
unIDBKeyPath
  {-# INLINE toJSVal #-}

instance FromJSVal IDBKeyPath where
  fromJSVal :: JSVal -> JSM (Maybe IDBKeyPath)
fromJSVal JSVal
v = (JSVal -> IDBKeyPath) -> Maybe JSVal -> Maybe IDBKeyPath
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBKeyPath
IDBKeyPath (Maybe JSVal -> Maybe IDBKeyPath)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBKeyPath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBKeyPath
fromJSValUnchecked = IDBKeyPath -> JSM IDBKeyPath
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBKeyPath -> JSM IDBKeyPath)
-> (JSVal -> IDBKeyPath) -> JSVal -> JSM IDBKeyPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBKeyPath
IDBKeyPath
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBKeyPath where
  makeObject :: IDBKeyPath -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBKeyPath -> JSVal) -> IDBKeyPath -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBKeyPath -> JSVal
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 { IDBRequestResult -> JSVal
unIDBRequestResult :: JSVal }

instance PToJSVal IDBRequestResult where
  pToJSVal :: IDBRequestResult -> JSVal
pToJSVal = IDBRequestResult -> JSVal
unIDBRequestResult
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBRequestResult where
  pFromJSVal :: JSVal -> IDBRequestResult
pFromJSVal = JSVal -> IDBRequestResult
IDBRequestResult
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBRequestResult where
  toJSVal :: IDBRequestResult -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBRequestResult -> JSVal) -> IDBRequestResult -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBRequestResult -> JSVal
unIDBRequestResult
  {-# INLINE toJSVal #-}

instance FromJSVal IDBRequestResult where
  fromJSVal :: JSVal -> JSM (Maybe IDBRequestResult)
fromJSVal JSVal
v = (JSVal -> IDBRequestResult)
-> Maybe JSVal -> Maybe IDBRequestResult
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBRequestResult
IDBRequestResult (Maybe JSVal -> Maybe IDBRequestResult)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBRequestResult)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBRequestResult
fromJSValUnchecked = IDBRequestResult -> JSM IDBRequestResult
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBRequestResult -> JSM IDBRequestResult)
-> (JSVal -> IDBRequestResult) -> JSVal -> JSM IDBRequestResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBRequestResult
IDBRequestResult
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBRequestResult where
  makeObject :: IDBRequestResult -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBRequestResult -> JSVal) -> IDBRequestResult -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBRequestResult -> JSVal
unIDBRequestResult

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBRequestResult o

toIDBRequestResult :: IsIDBRequestResult o => o -> IDBRequestResult
toIDBRequestResult :: forall o. IsIDBRequestResult o => o -> IDBRequestResult
toIDBRequestResult = JSVal -> IDBRequestResult
IDBRequestResult (JSVal -> IDBRequestResult)
-> (o -> JSVal) -> o -> IDBRequestResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsIDBRequestResult IDBRequestResult
instance IsIDBRequestResult JSVal
instance IsIDBRequestResult IDBDatabase
instance IsIDBRequestResult IDBCursor
instance IsIDBRequestResult IDBCursorWithValue

newtype IDBRequestSource = IDBRequestSource { IDBRequestSource -> JSVal
unIDBRequestSource :: JSVal }

instance PToJSVal IDBRequestSource where
  pToJSVal :: IDBRequestSource -> JSVal
pToJSVal = IDBRequestSource -> JSVal
unIDBRequestSource
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBRequestSource where
  pFromJSVal :: JSVal -> IDBRequestSource
pFromJSVal = JSVal -> IDBRequestSource
IDBRequestSource
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBRequestSource where
  toJSVal :: IDBRequestSource -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBRequestSource -> JSVal) -> IDBRequestSource -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBRequestSource -> JSVal
unIDBRequestSource
  {-# INLINE toJSVal #-}

instance FromJSVal IDBRequestSource where
  fromJSVal :: JSVal -> JSM (Maybe IDBRequestSource)
fromJSVal JSVal
v = (JSVal -> IDBRequestSource)
-> Maybe JSVal -> Maybe IDBRequestSource
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBRequestSource
IDBRequestSource (Maybe JSVal -> Maybe IDBRequestSource)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBRequestSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBRequestSource
fromJSValUnchecked = IDBRequestSource -> JSM IDBRequestSource
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBRequestSource -> JSM IDBRequestSource)
-> (JSVal -> IDBRequestSource) -> JSVal -> JSM IDBRequestSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBRequestSource
IDBRequestSource
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBRequestSource where
  makeObject :: IDBRequestSource -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBRequestSource -> JSVal) -> IDBRequestSource -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBRequestSource -> JSVal
unIDBRequestSource

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsIDBRequestSource o

toIDBRequestSource :: IsIDBRequestSource o => o -> IDBRequestSource
toIDBRequestSource :: forall o. IsIDBRequestSource o => o -> IDBRequestSource
toIDBRequestSource = JSVal -> IDBRequestSource
IDBRequestSource (JSVal -> IDBRequestSource)
-> (o -> JSVal) -> o -> IDBRequestSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsIDBRequestSource IDBRequestSource
instance IsIDBRequestSource IDBCursor
instance IsIDBRequestSource IDBCursorWithValue
instance IsIDBRequestSource IDBIndex
instance IsIDBRequestSource IDBObjectStore

newtype Int32List = Int32List { Int32List -> JSVal
unInt32List :: JSVal }

instance PToJSVal Int32List where
  pToJSVal :: Int32List -> JSVal
pToJSVal = Int32List -> JSVal
unInt32List
  {-# INLINE pToJSVal #-}

instance PFromJSVal Int32List where
  pFromJSVal :: JSVal -> Int32List
pFromJSVal = JSVal -> Int32List
Int32List
  {-# INLINE pFromJSVal #-}

instance ToJSVal Int32List where
  toJSVal :: Int32List -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Int32List -> JSVal) -> Int32List -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32List -> JSVal
unInt32List
  {-# INLINE toJSVal #-}

instance FromJSVal Int32List where
  fromJSVal :: JSVal -> JSM (Maybe Int32List)
fromJSVal JSVal
v = (JSVal -> Int32List) -> Maybe JSVal -> Maybe Int32List
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Int32List
Int32List (Maybe JSVal -> Maybe Int32List)
-> JSM (Maybe JSVal) -> JSM (Maybe Int32List)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Int32List
fromJSValUnchecked = Int32List -> JSM Int32List
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32List -> JSM Int32List)
-> (JSVal -> Int32List) -> JSVal -> JSM Int32List
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Int32List
Int32List
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Int32List where
  makeObject :: Int32List -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Int32List -> JSVal) -> Int32List -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32List -> JSVal
unInt32List

class (FromJSVal o, ToJSVal o) => IsInt32List o

instance IsInt32List Int32List
instance IsInt32List [GLint]
instance IsInt32List Int32Array

newtype KeyData = KeyData { KeyData -> JSVal
unKeyData :: JSVal }

instance PToJSVal KeyData where
  pToJSVal :: KeyData -> JSVal
pToJSVal = KeyData -> JSVal
unKeyData
  {-# INLINE pToJSVal #-}

instance PFromJSVal KeyData where
  pFromJSVal :: JSVal -> KeyData
pFromJSVal = JSVal -> KeyData
KeyData
  {-# INLINE pFromJSVal #-}

instance ToJSVal KeyData where
  toJSVal :: KeyData -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (KeyData -> JSVal) -> KeyData -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyData -> JSVal
unKeyData
  {-# INLINE toJSVal #-}

instance FromJSVal KeyData where
  fromJSVal :: JSVal -> JSM (Maybe KeyData)
fromJSVal JSVal
v = (JSVal -> KeyData) -> Maybe JSVal -> Maybe KeyData
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> KeyData
KeyData (Maybe JSVal -> Maybe KeyData)
-> JSM (Maybe JSVal) -> JSM (Maybe KeyData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM KeyData
fromJSValUnchecked = KeyData -> JSM KeyData
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyData -> JSM KeyData)
-> (JSVal -> KeyData) -> JSVal -> JSM KeyData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> KeyData
KeyData
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject KeyData where
  makeObject :: KeyData -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (KeyData -> JSVal) -> KeyData -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyData -> JSVal
unKeyData

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsKeyData o

toKeyData :: IsKeyData o => o -> KeyData
toKeyData :: forall o. IsKeyData o => o -> KeyData
toKeyData = JSVal -> KeyData
KeyData (JSVal -> KeyData) -> (o -> JSVal) -> o -> KeyData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsKeyData KeyData
instance IsKeyData JsonWebKey
instance IsKeyData BinaryData
instance IsKeyData BufferSource
instance IsKeyData ArrayBufferView
instance IsKeyData ArrayBuffer

newtype MediaProvider = MediaProvider { MediaProvider -> JSVal
unMediaProvider :: JSVal }

instance PToJSVal MediaProvider where
  pToJSVal :: MediaProvider -> JSVal
pToJSVal = MediaProvider -> JSVal
unMediaProvider
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaProvider where
  pFromJSVal :: JSVal -> MediaProvider
pFromJSVal = JSVal -> MediaProvider
MediaProvider
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaProvider where
  toJSVal :: MediaProvider -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaProvider -> JSVal) -> MediaProvider -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaProvider -> JSVal
unMediaProvider
  {-# INLINE toJSVal #-}

instance FromJSVal MediaProvider where
  fromJSVal :: JSVal -> JSM (Maybe MediaProvider)
fromJSVal JSVal
v = (JSVal -> MediaProvider) -> Maybe JSVal -> Maybe MediaProvider
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaProvider
MediaProvider (Maybe JSVal -> Maybe MediaProvider)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaProvider)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaProvider
fromJSValUnchecked = MediaProvider -> JSM MediaProvider
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaProvider -> JSM MediaProvider)
-> (JSVal -> MediaProvider) -> JSVal -> JSM MediaProvider
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaProvider
MediaProvider
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaProvider where
  makeObject :: MediaProvider -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaProvider -> JSVal) -> MediaProvider -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaProvider -> JSVal
unMediaProvider

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsMediaProvider o

toMediaProvider :: IsMediaProvider o => o -> MediaProvider
toMediaProvider :: forall o. IsMediaProvider o => o -> MediaProvider
toMediaProvider = JSVal -> MediaProvider
MediaProvider (JSVal -> MediaProvider) -> (o -> JSVal) -> o -> MediaProvider
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsMediaProvider MediaProvider
instance IsMediaProvider MediaStream
instance IsMediaProvider MediaSource
instance IsMediaProvider Blob
instance IsMediaProvider File

newtype MediaStreamTrackOrKind = MediaStreamTrackOrKind { MediaStreamTrackOrKind -> JSVal
unMediaStreamTrackOrKind :: JSVal }

instance PToJSVal MediaStreamTrackOrKind where
  pToJSVal :: MediaStreamTrackOrKind -> JSVal
pToJSVal = MediaStreamTrackOrKind -> JSVal
unMediaStreamTrackOrKind
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaStreamTrackOrKind where
  pFromJSVal :: JSVal -> MediaStreamTrackOrKind
pFromJSVal = JSVal -> MediaStreamTrackOrKind
MediaStreamTrackOrKind
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaStreamTrackOrKind where
  toJSVal :: MediaStreamTrackOrKind -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaStreamTrackOrKind -> JSVal)
-> MediaStreamTrackOrKind
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamTrackOrKind -> JSVal
unMediaStreamTrackOrKind
  {-# INLINE toJSVal #-}

instance FromJSVal MediaStreamTrackOrKind where
  fromJSVal :: JSVal -> JSM (Maybe MediaStreamTrackOrKind)
fromJSVal JSVal
v = (JSVal -> MediaStreamTrackOrKind)
-> Maybe JSVal -> Maybe MediaStreamTrackOrKind
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaStreamTrackOrKind
MediaStreamTrackOrKind (Maybe JSVal -> Maybe MediaStreamTrackOrKind)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaStreamTrackOrKind)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaStreamTrackOrKind
fromJSValUnchecked = MediaStreamTrackOrKind -> JSM MediaStreamTrackOrKind
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStreamTrackOrKind -> JSM MediaStreamTrackOrKind)
-> (JSVal -> MediaStreamTrackOrKind)
-> JSVal
-> JSM MediaStreamTrackOrKind
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaStreamTrackOrKind
MediaStreamTrackOrKind
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaStreamTrackOrKind where
  makeObject :: MediaStreamTrackOrKind -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaStreamTrackOrKind -> JSVal)
-> MediaStreamTrackOrKind
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamTrackOrKind -> JSVal
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 { MessageEventSource -> JSVal
unMessageEventSource :: JSVal }

instance PToJSVal MessageEventSource where
  pToJSVal :: MessageEventSource -> JSVal
pToJSVal = MessageEventSource -> JSVal
unMessageEventSource
  {-# INLINE pToJSVal #-}

instance PFromJSVal MessageEventSource where
  pFromJSVal :: JSVal -> MessageEventSource
pFromJSVal = JSVal -> MessageEventSource
MessageEventSource
  {-# INLINE pFromJSVal #-}

instance ToJSVal MessageEventSource where
  toJSVal :: MessageEventSource -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MessageEventSource -> JSVal) -> MessageEventSource -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageEventSource -> JSVal
unMessageEventSource
  {-# INLINE toJSVal #-}

instance FromJSVal MessageEventSource where
  fromJSVal :: JSVal -> JSM (Maybe MessageEventSource)
fromJSVal JSVal
v = (JSVal -> MessageEventSource)
-> Maybe JSVal -> Maybe MessageEventSource
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MessageEventSource
MessageEventSource (Maybe JSVal -> Maybe MessageEventSource)
-> JSM (Maybe JSVal) -> JSM (Maybe MessageEventSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MessageEventSource
fromJSValUnchecked = MessageEventSource -> JSM MessageEventSource
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MessageEventSource -> JSM MessageEventSource)
-> (JSVal -> MessageEventSource) -> JSVal -> JSM MessageEventSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MessageEventSource
MessageEventSource
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MessageEventSource where
  makeObject :: MessageEventSource -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MessageEventSource -> JSVal)
-> MessageEventSource
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageEventSource -> JSVal
unMessageEventSource

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsMessageEventSource o

toMessageEventSource :: IsMessageEventSource o => o -> MessageEventSource
toMessageEventSource :: forall o. IsMessageEventSource o => o -> MessageEventSource
toMessageEventSource = JSVal -> MessageEventSource
MessageEventSource (JSVal -> MessageEventSource)
-> (o -> JSVal) -> o -> MessageEventSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsMessageEventSource MessageEventSource
instance IsMessageEventSource MessagePort
instance IsMessageEventSource Window

newtype NodeOrString = NodeOrString { NodeOrString -> JSVal
unNodeOrString :: JSVal }

instance PToJSVal NodeOrString where
  pToJSVal :: NodeOrString -> JSVal
pToJSVal = NodeOrString -> JSVal
unNodeOrString
  {-# INLINE pToJSVal #-}

instance PFromJSVal NodeOrString where
  pFromJSVal :: JSVal -> NodeOrString
pFromJSVal = JSVal -> NodeOrString
NodeOrString
  {-# INLINE pFromJSVal #-}

instance ToJSVal NodeOrString where
  toJSVal :: NodeOrString -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NodeOrString -> JSVal) -> NodeOrString -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NodeOrString -> JSVal
unNodeOrString
  {-# INLINE toJSVal #-}

instance FromJSVal NodeOrString where
  fromJSVal :: JSVal -> JSM (Maybe NodeOrString)
fromJSVal JSVal
v = (JSVal -> NodeOrString) -> Maybe JSVal -> Maybe NodeOrString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NodeOrString
NodeOrString (Maybe JSVal -> Maybe NodeOrString)
-> JSM (Maybe JSVal) -> JSM (Maybe NodeOrString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NodeOrString
fromJSValUnchecked = NodeOrString -> JSM NodeOrString
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NodeOrString -> JSM NodeOrString)
-> (JSVal -> NodeOrString) -> JSVal -> JSM NodeOrString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NodeOrString
NodeOrString
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NodeOrString where
  makeObject :: NodeOrString -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NodeOrString -> JSVal) -> NodeOrString -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NodeOrString -> JSVal
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 { RTCIceCandidateOrInit -> JSVal
unRTCIceCandidateOrInit :: JSVal }

instance PToJSVal RTCIceCandidateOrInit where
  pToJSVal :: RTCIceCandidateOrInit -> JSVal
pToJSVal = RTCIceCandidateOrInit -> JSVal
unRTCIceCandidateOrInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCIceCandidateOrInit where
  pFromJSVal :: JSVal -> RTCIceCandidateOrInit
pFromJSVal = JSVal -> RTCIceCandidateOrInit
RTCIceCandidateOrInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCIceCandidateOrInit where
  toJSVal :: RTCIceCandidateOrInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCIceCandidateOrInit -> JSVal)
-> RTCIceCandidateOrInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceCandidateOrInit -> JSVal
unRTCIceCandidateOrInit
  {-# INLINE toJSVal #-}

instance FromJSVal RTCIceCandidateOrInit where
  fromJSVal :: JSVal -> JSM (Maybe RTCIceCandidateOrInit)
fromJSVal JSVal
v = (JSVal -> RTCIceCandidateOrInit)
-> Maybe JSVal -> Maybe RTCIceCandidateOrInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCIceCandidateOrInit
RTCIceCandidateOrInit (Maybe JSVal -> Maybe RTCIceCandidateOrInit)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCIceCandidateOrInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCIceCandidateOrInit
fromJSValUnchecked = RTCIceCandidateOrInit -> JSM RTCIceCandidateOrInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceCandidateOrInit -> JSM RTCIceCandidateOrInit)
-> (JSVal -> RTCIceCandidateOrInit)
-> JSVal
-> JSM RTCIceCandidateOrInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCIceCandidateOrInit
RTCIceCandidateOrInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCIceCandidateOrInit where
  makeObject :: RTCIceCandidateOrInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCIceCandidateOrInit -> JSVal)
-> RTCIceCandidateOrInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceCandidateOrInit -> JSVal
unRTCIceCandidateOrInit

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRTCIceCandidateOrInit o

toRTCIceCandidateOrInit :: IsRTCIceCandidateOrInit o => o -> RTCIceCandidateOrInit
toRTCIceCandidateOrInit :: forall o. IsRTCIceCandidateOrInit o => o -> RTCIceCandidateOrInit
toRTCIceCandidateOrInit = JSVal -> RTCIceCandidateOrInit
RTCIceCandidateOrInit (JSVal -> RTCIceCandidateOrInit)
-> (o -> JSVal) -> o -> RTCIceCandidateOrInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsRTCIceCandidateOrInit RTCIceCandidateOrInit
instance IsRTCIceCandidateOrInit RTCIceCandidate
instance IsRTCIceCandidateOrInit RTCIceCandidateInit

newtype RadioNodeListOrElement = RadioNodeListOrElement { RadioNodeListOrElement -> JSVal
unRadioNodeListOrElement :: JSVal }

instance PToJSVal RadioNodeListOrElement where
  pToJSVal :: RadioNodeListOrElement -> JSVal
pToJSVal = RadioNodeListOrElement -> JSVal
unRadioNodeListOrElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal RadioNodeListOrElement where
  pFromJSVal :: JSVal -> RadioNodeListOrElement
pFromJSVal = JSVal -> RadioNodeListOrElement
RadioNodeListOrElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal RadioNodeListOrElement where
  toJSVal :: RadioNodeListOrElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RadioNodeListOrElement -> JSVal)
-> RadioNodeListOrElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RadioNodeListOrElement -> JSVal
unRadioNodeListOrElement
  {-# INLINE toJSVal #-}

instance FromJSVal RadioNodeListOrElement where
  fromJSVal :: JSVal -> JSM (Maybe RadioNodeListOrElement)
fromJSVal JSVal
v = (JSVal -> RadioNodeListOrElement)
-> Maybe JSVal -> Maybe RadioNodeListOrElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RadioNodeListOrElement
RadioNodeListOrElement (Maybe JSVal -> Maybe RadioNodeListOrElement)
-> JSM (Maybe JSVal) -> JSM (Maybe RadioNodeListOrElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RadioNodeListOrElement
fromJSValUnchecked = RadioNodeListOrElement -> JSM RadioNodeListOrElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RadioNodeListOrElement -> JSM RadioNodeListOrElement)
-> (JSVal -> RadioNodeListOrElement)
-> JSVal
-> JSM RadioNodeListOrElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RadioNodeListOrElement
RadioNodeListOrElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RadioNodeListOrElement where
  makeObject :: RadioNodeListOrElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RadioNodeListOrElement -> JSVal)
-> RadioNodeListOrElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RadioNodeListOrElement -> JSVal
unRadioNodeListOrElement

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRadioNodeListOrElement o

toRadioNodeListOrElement :: IsRadioNodeListOrElement o => o -> RadioNodeListOrElement
toRadioNodeListOrElement :: forall o. IsRadioNodeListOrElement o => o -> RadioNodeListOrElement
toRadioNodeListOrElement = JSVal -> RadioNodeListOrElement
RadioNodeListOrElement (JSVal -> RadioNodeListOrElement)
-> (o -> JSVal) -> o -> RadioNodeListOrElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 { RenderingContext -> JSVal
unRenderingContext :: JSVal }

instance PToJSVal RenderingContext where
  pToJSVal :: RenderingContext -> JSVal
pToJSVal = RenderingContext -> JSVal
unRenderingContext
  {-# INLINE pToJSVal #-}

instance PFromJSVal RenderingContext where
  pFromJSVal :: JSVal -> RenderingContext
pFromJSVal = JSVal -> RenderingContext
RenderingContext
  {-# INLINE pFromJSVal #-}

instance ToJSVal RenderingContext where
  toJSVal :: RenderingContext -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RenderingContext -> JSVal) -> RenderingContext -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderingContext -> JSVal
unRenderingContext
  {-# INLINE toJSVal #-}

instance FromJSVal RenderingContext where
  fromJSVal :: JSVal -> JSM (Maybe RenderingContext)
fromJSVal JSVal
v = (JSVal -> RenderingContext)
-> Maybe JSVal -> Maybe RenderingContext
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RenderingContext
RenderingContext (Maybe JSVal -> Maybe RenderingContext)
-> JSM (Maybe JSVal) -> JSM (Maybe RenderingContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RenderingContext
fromJSValUnchecked = RenderingContext -> JSM RenderingContext
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RenderingContext -> JSM RenderingContext)
-> (JSVal -> RenderingContext) -> JSVal -> JSM RenderingContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RenderingContext
RenderingContext
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RenderingContext where
  makeObject :: RenderingContext -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RenderingContext -> JSVal) -> RenderingContext -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderingContext -> JSVal
unRenderingContext

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsRenderingContext o

toRenderingContext :: IsRenderingContext o => o -> RenderingContext
toRenderingContext :: forall o. IsRenderingContext o => o -> RenderingContext
toRenderingContext = JSVal -> RenderingContext
RenderingContext (JSVal -> RenderingContext)
-> (o -> JSVal) -> o -> RenderingContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsRenderingContext RenderingContext
instance IsRenderingContext WebGLRenderingContextBase
instance IsRenderingContext WebGLRenderingContext
instance IsRenderingContext WebGL2RenderingContext
instance IsRenderingContext CanvasRenderingContext2D

newtype SQLValue = SQLValue { SQLValue -> JSVal
unSQLValue :: JSVal }

instance PToJSVal SQLValue where
  pToJSVal :: SQLValue -> JSVal
pToJSVal = SQLValue -> JSVal
unSQLValue
  {-# INLINE pToJSVal #-}

instance PFromJSVal SQLValue where
  pFromJSVal :: JSVal -> SQLValue
pFromJSVal = JSVal -> SQLValue
SQLValue
  {-# INLINE pFromJSVal #-}

instance ToJSVal SQLValue where
  toJSVal :: SQLValue -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SQLValue -> JSVal) -> SQLValue -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLValue -> JSVal
unSQLValue
  {-# INLINE toJSVal #-}

instance FromJSVal SQLValue where
  fromJSVal :: JSVal -> JSM (Maybe SQLValue)
fromJSVal JSVal
v = (JSVal -> SQLValue) -> Maybe JSVal -> Maybe SQLValue
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SQLValue
SQLValue (Maybe JSVal -> Maybe SQLValue)
-> JSM (Maybe JSVal) -> JSM (Maybe SQLValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SQLValue
fromJSValUnchecked = SQLValue -> JSM SQLValue
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SQLValue -> JSM SQLValue)
-> (JSVal -> SQLValue) -> JSVal -> JSM SQLValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SQLValue
SQLValue
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SQLValue where
  makeObject :: SQLValue -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SQLValue -> JSVal) -> SQLValue -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLValue -> JSVal
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 { StringOrArrayBuffer -> JSVal
unStringOrArrayBuffer :: JSVal }

instance PToJSVal StringOrArrayBuffer where
  pToJSVal :: StringOrArrayBuffer -> JSVal
pToJSVal = StringOrArrayBuffer -> JSVal
unStringOrArrayBuffer
  {-# INLINE pToJSVal #-}

instance PFromJSVal StringOrArrayBuffer where
  pFromJSVal :: JSVal -> StringOrArrayBuffer
pFromJSVal = JSVal -> StringOrArrayBuffer
StringOrArrayBuffer
  {-# INLINE pFromJSVal #-}

instance ToJSVal StringOrArrayBuffer where
  toJSVal :: StringOrArrayBuffer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (StringOrArrayBuffer -> JSVal)
-> StringOrArrayBuffer
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StringOrArrayBuffer -> JSVal
unStringOrArrayBuffer
  {-# INLINE toJSVal #-}

instance FromJSVal StringOrArrayBuffer where
  fromJSVal :: JSVal -> JSM (Maybe StringOrArrayBuffer)
fromJSVal JSVal
v = (JSVal -> StringOrArrayBuffer)
-> Maybe JSVal -> Maybe StringOrArrayBuffer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> StringOrArrayBuffer
StringOrArrayBuffer (Maybe JSVal -> Maybe StringOrArrayBuffer)
-> JSM (Maybe JSVal) -> JSM (Maybe StringOrArrayBuffer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM StringOrArrayBuffer
fromJSValUnchecked = StringOrArrayBuffer -> JSM StringOrArrayBuffer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (StringOrArrayBuffer -> JSM StringOrArrayBuffer)
-> (JSVal -> StringOrArrayBuffer)
-> JSVal
-> JSM StringOrArrayBuffer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> StringOrArrayBuffer
StringOrArrayBuffer
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject StringOrArrayBuffer where
  makeObject :: StringOrArrayBuffer -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (StringOrArrayBuffer -> JSVal)
-> StringOrArrayBuffer
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StringOrArrayBuffer -> JSVal
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 { StringOrBinaryData -> JSVal
unStringOrBinaryData :: JSVal }

instance PToJSVal StringOrBinaryData where
  pToJSVal :: StringOrBinaryData -> JSVal
pToJSVal = StringOrBinaryData -> JSVal
unStringOrBinaryData
  {-# INLINE pToJSVal #-}

instance PFromJSVal StringOrBinaryData where
  pFromJSVal :: JSVal -> StringOrBinaryData
pFromJSVal = JSVal -> StringOrBinaryData
StringOrBinaryData
  {-# INLINE pFromJSVal #-}

instance ToJSVal StringOrBinaryData where
  toJSVal :: StringOrBinaryData -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (StringOrBinaryData -> JSVal) -> StringOrBinaryData -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StringOrBinaryData -> JSVal
unStringOrBinaryData
  {-# INLINE toJSVal #-}

instance FromJSVal StringOrBinaryData where
  fromJSVal :: JSVal -> JSM (Maybe StringOrBinaryData)
fromJSVal JSVal
v = (JSVal -> StringOrBinaryData)
-> Maybe JSVal -> Maybe StringOrBinaryData
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> StringOrBinaryData
StringOrBinaryData (Maybe JSVal -> Maybe StringOrBinaryData)
-> JSM (Maybe JSVal) -> JSM (Maybe StringOrBinaryData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM StringOrBinaryData
fromJSValUnchecked = StringOrBinaryData -> JSM StringOrBinaryData
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (StringOrBinaryData -> JSM StringOrBinaryData)
-> (JSVal -> StringOrBinaryData) -> JSVal -> JSM StringOrBinaryData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> StringOrBinaryData
StringOrBinaryData
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject StringOrBinaryData where
  makeObject :: StringOrBinaryData -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (StringOrBinaryData -> JSVal)
-> StringOrBinaryData
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StringOrBinaryData -> JSVal
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 { StringOrStrings -> JSVal
unStringOrStrings :: JSVal }

instance PToJSVal StringOrStrings where
  pToJSVal :: StringOrStrings -> JSVal
pToJSVal = StringOrStrings -> JSVal
unStringOrStrings
  {-# INLINE pToJSVal #-}

instance PFromJSVal StringOrStrings where
  pFromJSVal :: JSVal -> StringOrStrings
pFromJSVal = JSVal -> StringOrStrings
StringOrStrings
  {-# INLINE pFromJSVal #-}

instance ToJSVal StringOrStrings where
  toJSVal :: StringOrStrings -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (StringOrStrings -> JSVal) -> StringOrStrings -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StringOrStrings -> JSVal
unStringOrStrings
  {-# INLINE toJSVal #-}

instance FromJSVal StringOrStrings where
  fromJSVal :: JSVal -> JSM (Maybe StringOrStrings)
fromJSVal JSVal
v = (JSVal -> StringOrStrings) -> Maybe JSVal -> Maybe StringOrStrings
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> StringOrStrings
StringOrStrings (Maybe JSVal -> Maybe StringOrStrings)
-> JSM (Maybe JSVal) -> JSM (Maybe StringOrStrings)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM StringOrStrings
fromJSValUnchecked = StringOrStrings -> JSM StringOrStrings
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (StringOrStrings -> JSM StringOrStrings)
-> (JSVal -> StringOrStrings) -> JSVal -> JSM StringOrStrings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> StringOrStrings
StringOrStrings
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject StringOrStrings where
  makeObject :: StringOrStrings -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (StringOrStrings -> JSVal) -> StringOrStrings -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StringOrStrings -> JSVal
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 { TexImageSource -> JSVal
unTexImageSource :: JSVal }

instance PToJSVal TexImageSource where
  pToJSVal :: TexImageSource -> JSVal
pToJSVal = TexImageSource -> JSVal
unTexImageSource
  {-# INLINE pToJSVal #-}

instance PFromJSVal TexImageSource where
  pFromJSVal :: JSVal -> TexImageSource
pFromJSVal = JSVal -> TexImageSource
TexImageSource
  {-# INLINE pFromJSVal #-}

instance ToJSVal TexImageSource where
  toJSVal :: TexImageSource -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TexImageSource -> JSVal) -> TexImageSource -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TexImageSource -> JSVal
unTexImageSource
  {-# INLINE toJSVal #-}

instance FromJSVal TexImageSource where
  fromJSVal :: JSVal -> JSM (Maybe TexImageSource)
fromJSVal JSVal
v = (JSVal -> TexImageSource) -> Maybe JSVal -> Maybe TexImageSource
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TexImageSource
TexImageSource (Maybe JSVal -> Maybe TexImageSource)
-> JSM (Maybe JSVal) -> JSM (Maybe TexImageSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TexImageSource
fromJSValUnchecked = TexImageSource -> JSM TexImageSource
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TexImageSource -> JSM TexImageSource)
-> (JSVal -> TexImageSource) -> JSVal -> JSM TexImageSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TexImageSource
TexImageSource
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TexImageSource where
  makeObject :: TexImageSource -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TexImageSource -> JSVal) -> TexImageSource -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TexImageSource -> JSVal
unTexImageSource

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsTexImageSource o

toTexImageSource :: IsTexImageSource o => o -> TexImageSource
toTexImageSource :: forall o. IsTexImageSource o => o -> TexImageSource
toTexImageSource = JSVal -> TexImageSource
TexImageSource (JSVal -> TexImageSource) -> (o -> JSVal) -> o -> TexImageSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsTexImageSource TexImageSource
instance IsTexImageSource ImageData
instance IsTexImageSource HTMLImageElement
instance IsTexImageSource HTMLVideoElement
instance IsTexImageSource HTMLCanvasElement

newtype Track = Track { Track -> JSVal
unTrack :: JSVal }

instance PToJSVal Track where
  pToJSVal :: Track -> JSVal
pToJSVal = Track -> JSVal
unTrack
  {-# INLINE pToJSVal #-}

instance PFromJSVal Track where
  pFromJSVal :: JSVal -> Track
pFromJSVal = JSVal -> Track
Track
  {-# INLINE pFromJSVal #-}

instance ToJSVal Track where
  toJSVal :: Track -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Track -> JSVal) -> Track -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Track -> JSVal
unTrack
  {-# INLINE toJSVal #-}

instance FromJSVal Track where
  fromJSVal :: JSVal -> JSM (Maybe Track)
fromJSVal JSVal
v = (JSVal -> Track) -> Maybe JSVal -> Maybe Track
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Track
Track (Maybe JSVal -> Maybe Track)
-> JSM (Maybe JSVal) -> JSM (Maybe Track)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Track
fromJSValUnchecked = Track -> JSM Track
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Track -> JSM Track) -> (JSVal -> Track) -> JSVal -> JSM Track
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Track
Track
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Track where
  makeObject :: Track -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Track -> JSVal) -> Track -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Track -> JSVal
unTrack

class (FromJSVal o, ToJSVal o, PFromJSVal o, PToJSVal o, Coercible o JSVal) => IsTrack o

toTrack :: IsTrack o => o -> Track
toTrack :: forall o. IsTrack o => o -> Track
toTrack = JSVal -> Track
Track (JSVal -> Track) -> (o -> JSVal) -> o -> Track
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsTrack Track
instance IsTrack TextTrack
instance IsTrack AudioTrack
instance IsTrack VideoTrack

newtype URLSearchParamsInit = URLSearchParamsInit { URLSearchParamsInit -> JSVal
unURLSearchParamsInit :: JSVal }

instance PToJSVal URLSearchParamsInit where
  pToJSVal :: URLSearchParamsInit -> JSVal
pToJSVal = URLSearchParamsInit -> JSVal
unURLSearchParamsInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal URLSearchParamsInit where
  pFromJSVal :: JSVal -> URLSearchParamsInit
pFromJSVal = JSVal -> URLSearchParamsInit
URLSearchParamsInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal URLSearchParamsInit where
  toJSVal :: URLSearchParamsInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (URLSearchParamsInit -> JSVal)
-> URLSearchParamsInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URLSearchParamsInit -> JSVal
unURLSearchParamsInit
  {-# INLINE toJSVal #-}

instance FromJSVal URLSearchParamsInit where
  fromJSVal :: JSVal -> JSM (Maybe URLSearchParamsInit)
fromJSVal JSVal
v = (JSVal -> URLSearchParamsInit)
-> Maybe JSVal -> Maybe URLSearchParamsInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> URLSearchParamsInit
URLSearchParamsInit (Maybe JSVal -> Maybe URLSearchParamsInit)
-> JSM (Maybe JSVal) -> JSM (Maybe URLSearchParamsInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM URLSearchParamsInit
fromJSValUnchecked = URLSearchParamsInit -> JSM URLSearchParamsInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (URLSearchParamsInit -> JSM URLSearchParamsInit)
-> (JSVal -> URLSearchParamsInit)
-> JSVal
-> JSM URLSearchParamsInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> URLSearchParamsInit
URLSearchParamsInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject URLSearchParamsInit where
  makeObject :: URLSearchParamsInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (URLSearchParamsInit -> JSVal)
-> URLSearchParamsInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URLSearchParamsInit -> JSVal
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 { XMLHttpRequestBody -> JSVal
unXMLHttpRequestBody :: JSVal }

instance PToJSVal XMLHttpRequestBody where
  pToJSVal :: XMLHttpRequestBody -> JSVal
pToJSVal = XMLHttpRequestBody -> JSVal
unXMLHttpRequestBody
  {-# INLINE pToJSVal #-}

instance PFromJSVal XMLHttpRequestBody where
  pFromJSVal :: JSVal -> XMLHttpRequestBody
pFromJSVal = JSVal -> XMLHttpRequestBody
XMLHttpRequestBody
  {-# INLINE pFromJSVal #-}

instance ToJSVal XMLHttpRequestBody where
  toJSVal :: XMLHttpRequestBody -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XMLHttpRequestBody -> JSVal) -> XMLHttpRequestBody -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLHttpRequestBody -> JSVal
unXMLHttpRequestBody
  {-# INLINE toJSVal #-}

instance FromJSVal XMLHttpRequestBody where
  fromJSVal :: JSVal -> JSM (Maybe XMLHttpRequestBody)
fromJSVal JSVal
v = (JSVal -> XMLHttpRequestBody)
-> Maybe JSVal -> Maybe XMLHttpRequestBody
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XMLHttpRequestBody
XMLHttpRequestBody (Maybe JSVal -> Maybe XMLHttpRequestBody)
-> JSM (Maybe JSVal) -> JSM (Maybe XMLHttpRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XMLHttpRequestBody
fromJSValUnchecked = XMLHttpRequestBody -> JSM XMLHttpRequestBody
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XMLHttpRequestBody -> JSM XMLHttpRequestBody)
-> (JSVal -> XMLHttpRequestBody) -> JSVal -> JSM XMLHttpRequestBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XMLHttpRequestBody
XMLHttpRequestBody
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XMLHttpRequestBody where
  makeObject :: XMLHttpRequestBody -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XMLHttpRequestBody -> JSVal)
-> XMLHttpRequestBody
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLHttpRequestBody -> JSVal
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


-- | Functions for this inteface are in "JSDOM.ANGLEInstancedArrays".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ANGLEInstancedArrays Mozilla ANGLEInstancedArrays documentation>
newtype ANGLEInstancedArrays = ANGLEInstancedArrays { ANGLEInstancedArrays -> JSVal
unANGLEInstancedArrays :: JSVal }

instance PToJSVal ANGLEInstancedArrays where
  pToJSVal :: ANGLEInstancedArrays -> JSVal
pToJSVal = ANGLEInstancedArrays -> JSVal
unANGLEInstancedArrays
  {-# INLINE pToJSVal #-}

instance PFromJSVal ANGLEInstancedArrays where
  pFromJSVal :: JSVal -> ANGLEInstancedArrays
pFromJSVal = JSVal -> ANGLEInstancedArrays
ANGLEInstancedArrays
  {-# INLINE pFromJSVal #-}

instance ToJSVal ANGLEInstancedArrays where
  toJSVal :: ANGLEInstancedArrays -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ANGLEInstancedArrays -> JSVal)
-> ANGLEInstancedArrays
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ANGLEInstancedArrays -> JSVal
unANGLEInstancedArrays
  {-# INLINE toJSVal #-}

instance FromJSVal ANGLEInstancedArrays where
  fromJSVal :: JSVal -> JSM (Maybe ANGLEInstancedArrays)
fromJSVal JSVal
v = (JSVal -> ANGLEInstancedArrays)
-> Maybe JSVal -> Maybe ANGLEInstancedArrays
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ANGLEInstancedArrays
ANGLEInstancedArrays (Maybe JSVal -> Maybe ANGLEInstancedArrays)
-> JSM (Maybe JSVal) -> JSM (Maybe ANGLEInstancedArrays)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ANGLEInstancedArrays
fromJSValUnchecked = ANGLEInstancedArrays -> JSM ANGLEInstancedArrays
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ANGLEInstancedArrays -> JSM ANGLEInstancedArrays)
-> (JSVal -> ANGLEInstancedArrays)
-> JSVal
-> JSM ANGLEInstancedArrays
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ANGLEInstancedArrays
ANGLEInstancedArrays
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ANGLEInstancedArrays where
  makeObject :: ANGLEInstancedArrays -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ANGLEInstancedArrays -> JSVal)
-> ANGLEInstancedArrays
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ANGLEInstancedArrays -> JSVal
unANGLEInstancedArrays

instance IsGObject ANGLEInstancedArrays where
  typeGType :: ANGLEInstancedArrays -> JSM GType
typeGType ANGLEInstancedArrays
_ = JSM GType
gTypeANGLEInstancedArrays
  {-# INLINE typeGType #-}

noANGLEInstancedArrays :: Maybe ANGLEInstancedArrays
noANGLEInstancedArrays :: Maybe ANGLEInstancedArrays
noANGLEInstancedArrays = Maybe ANGLEInstancedArrays
forall a. Maybe a
Nothing
{-# INLINE noANGLEInstancedArrays #-}

gTypeANGLEInstancedArrays :: JSM GType
gTypeANGLEInstancedArrays :: JSM GType
gTypeANGLEInstancedArrays = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ANGLEInstancedArrays"

-- | Functions for this inteface are in "JSDOM.AbstractWorker".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AbstractWorker Mozilla AbstractWorker documentation>
newtype AbstractWorker = AbstractWorker { AbstractWorker -> JSVal
unAbstractWorker :: JSVal }

instance PToJSVal AbstractWorker where
  pToJSVal :: AbstractWorker -> JSVal
pToJSVal = AbstractWorker -> JSVal
unAbstractWorker
  {-# INLINE pToJSVal #-}

instance PFromJSVal AbstractWorker where
  pFromJSVal :: JSVal -> AbstractWorker
pFromJSVal = JSVal -> AbstractWorker
AbstractWorker
  {-# INLINE pFromJSVal #-}

instance ToJSVal AbstractWorker where
  toJSVal :: AbstractWorker -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AbstractWorker -> JSVal) -> AbstractWorker -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AbstractWorker -> JSVal
unAbstractWorker
  {-# INLINE toJSVal #-}

instance FromJSVal AbstractWorker where
  fromJSVal :: JSVal -> JSM (Maybe AbstractWorker)
fromJSVal JSVal
v = (JSVal -> AbstractWorker) -> Maybe JSVal -> Maybe AbstractWorker
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AbstractWorker
AbstractWorker (Maybe JSVal -> Maybe AbstractWorker)
-> JSM (Maybe JSVal) -> JSM (Maybe AbstractWorker)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AbstractWorker
fromJSValUnchecked = AbstractWorker -> JSM AbstractWorker
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AbstractWorker -> JSM AbstractWorker)
-> (JSVal -> AbstractWorker) -> JSVal -> JSM AbstractWorker
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AbstractWorker
AbstractWorker
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AbstractWorker where
  makeObject :: AbstractWorker -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AbstractWorker -> JSVal) -> AbstractWorker -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AbstractWorker -> JSVal
unAbstractWorker

class (IsGObject o) => IsAbstractWorker o
toAbstractWorker :: IsAbstractWorker o => o -> AbstractWorker
toAbstractWorker :: forall o. IsAbstractWorker o => o -> AbstractWorker
toAbstractWorker = JSVal -> AbstractWorker
AbstractWorker (JSVal -> AbstractWorker) -> (o -> JSVal) -> o -> AbstractWorker
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsAbstractWorker AbstractWorker
instance IsGObject AbstractWorker where
  typeGType :: AbstractWorker -> JSM GType
typeGType AbstractWorker
_ = JSM GType
gTypeAbstractWorker
  {-# INLINE typeGType #-}

noAbstractWorker :: Maybe AbstractWorker
noAbstractWorker :: Maybe AbstractWorker
noAbstractWorker = Maybe AbstractWorker
forall a. Maybe a
Nothing
{-# INLINE noAbstractWorker #-}

gTypeAbstractWorker :: JSM GType
gTypeAbstractWorker :: JSM GType
gTypeAbstractWorker = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AbstractWorker"

-- | Functions for this inteface are in "JSDOM.Acceleration".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Acceleration Mozilla Acceleration documentation>
newtype Acceleration = Acceleration { Acceleration -> JSVal
unAcceleration :: JSVal }

instance PToJSVal Acceleration where
  pToJSVal :: Acceleration -> JSVal
pToJSVal = Acceleration -> JSVal
unAcceleration
  {-# INLINE pToJSVal #-}

instance PFromJSVal Acceleration where
  pFromJSVal :: JSVal -> Acceleration
pFromJSVal = JSVal -> Acceleration
Acceleration
  {-# INLINE pFromJSVal #-}

instance ToJSVal Acceleration where
  toJSVal :: Acceleration -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Acceleration -> JSVal) -> Acceleration -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Acceleration -> JSVal
unAcceleration
  {-# INLINE toJSVal #-}

instance FromJSVal Acceleration where
  fromJSVal :: JSVal -> JSM (Maybe Acceleration)
fromJSVal JSVal
v = (JSVal -> Acceleration) -> Maybe JSVal -> Maybe Acceleration
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Acceleration
Acceleration (Maybe JSVal -> Maybe Acceleration)
-> JSM (Maybe JSVal) -> JSM (Maybe Acceleration)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Acceleration
fromJSValUnchecked = Acceleration -> JSM Acceleration
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Acceleration -> JSM Acceleration)
-> (JSVal -> Acceleration) -> JSVal -> JSM Acceleration
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Acceleration
Acceleration
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Acceleration where
  makeObject :: Acceleration -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Acceleration -> JSVal) -> Acceleration -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Acceleration -> JSVal
unAcceleration

instance IsGObject Acceleration where
  typeGType :: Acceleration -> JSM GType
typeGType Acceleration
_ = JSM GType
gTypeAcceleration
  {-# INLINE typeGType #-}

noAcceleration :: Maybe Acceleration
noAcceleration :: Maybe Acceleration
noAcceleration = Maybe Acceleration
forall a. Maybe a
Nothing
{-# INLINE noAcceleration #-}

gTypeAcceleration :: JSM GType
gTypeAcceleration :: JSM GType
gTypeAcceleration = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Acceleration"

-- | Functions for this inteface are in "JSDOM.AddEventListenerOptions".
-- Base interface functions are in:
--
--     * "JSDOM.EventListenerOptions"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AddEventListenerOptions Mozilla AddEventListenerOptions documentation>
newtype AddEventListenerOptions = AddEventListenerOptions { AddEventListenerOptions -> JSVal
unAddEventListenerOptions :: JSVal }

instance PToJSVal AddEventListenerOptions where
  pToJSVal :: AddEventListenerOptions -> JSVal
pToJSVal = AddEventListenerOptions -> JSVal
unAddEventListenerOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal AddEventListenerOptions where
  pFromJSVal :: JSVal -> AddEventListenerOptions
pFromJSVal = JSVal -> AddEventListenerOptions
AddEventListenerOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal AddEventListenerOptions where
  toJSVal :: AddEventListenerOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AddEventListenerOptions -> JSVal)
-> AddEventListenerOptions
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AddEventListenerOptions -> JSVal
unAddEventListenerOptions
  {-# INLINE toJSVal #-}

instance FromJSVal AddEventListenerOptions where
  fromJSVal :: JSVal -> JSM (Maybe AddEventListenerOptions)
fromJSVal JSVal
v = (JSVal -> AddEventListenerOptions)
-> Maybe JSVal -> Maybe AddEventListenerOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AddEventListenerOptions
AddEventListenerOptions (Maybe JSVal -> Maybe AddEventListenerOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe AddEventListenerOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AddEventListenerOptions
fromJSValUnchecked = AddEventListenerOptions -> JSM AddEventListenerOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AddEventListenerOptions -> JSM AddEventListenerOptions)
-> (JSVal -> AddEventListenerOptions)
-> JSVal
-> JSM AddEventListenerOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AddEventListenerOptions
AddEventListenerOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AddEventListenerOptions where
  makeObject :: AddEventListenerOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AddEventListenerOptions -> JSVal)
-> AddEventListenerOptions
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AddEventListenerOptions -> JSVal
unAddEventListenerOptions

instance IsEventListenerOptions AddEventListenerOptions
instance IsGObject AddEventListenerOptions where
  typeGType :: AddEventListenerOptions -> JSM GType
typeGType AddEventListenerOptions
_ = JSM GType
gTypeAddEventListenerOptions
  {-# INLINE typeGType #-}

noAddEventListenerOptions :: Maybe AddEventListenerOptions
noAddEventListenerOptions :: Maybe AddEventListenerOptions
noAddEventListenerOptions = Maybe AddEventListenerOptions
forall a. Maybe a
Nothing
{-# INLINE noAddEventListenerOptions #-}

gTypeAddEventListenerOptions :: JSM GType
gTypeAddEventListenerOptions :: JSM GType
gTypeAddEventListenerOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AddEventListenerOptions"

-- | Functions for this inteface are in "JSDOM.AesCbcCfbParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AesCbcCfbParams Mozilla AesCbcCfbParams documentation>
newtype AesCbcCfbParams = AesCbcCfbParams { AesCbcCfbParams -> JSVal
unAesCbcCfbParams :: JSVal }

instance PToJSVal AesCbcCfbParams where
  pToJSVal :: AesCbcCfbParams -> JSVal
pToJSVal = AesCbcCfbParams -> JSVal
unAesCbcCfbParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal AesCbcCfbParams where
  pFromJSVal :: JSVal -> AesCbcCfbParams
pFromJSVal = JSVal -> AesCbcCfbParams
AesCbcCfbParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal AesCbcCfbParams where
  toJSVal :: AesCbcCfbParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AesCbcCfbParams -> JSVal) -> AesCbcCfbParams -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AesCbcCfbParams -> JSVal
unAesCbcCfbParams
  {-# INLINE toJSVal #-}

instance FromJSVal AesCbcCfbParams where
  fromJSVal :: JSVal -> JSM (Maybe AesCbcCfbParams)
fromJSVal JSVal
v = (JSVal -> AesCbcCfbParams) -> Maybe JSVal -> Maybe AesCbcCfbParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AesCbcCfbParams
AesCbcCfbParams (Maybe JSVal -> Maybe AesCbcCfbParams)
-> JSM (Maybe JSVal) -> JSM (Maybe AesCbcCfbParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AesCbcCfbParams
fromJSValUnchecked = AesCbcCfbParams -> JSM AesCbcCfbParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AesCbcCfbParams -> JSM AesCbcCfbParams)
-> (JSVal -> AesCbcCfbParams) -> JSVal -> JSM AesCbcCfbParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AesCbcCfbParams
AesCbcCfbParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AesCbcCfbParams where
  makeObject :: AesCbcCfbParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AesCbcCfbParams -> JSVal) -> AesCbcCfbParams -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AesCbcCfbParams -> JSVal
unAesCbcCfbParams

instance IsCryptoAlgorithmParameters AesCbcCfbParams
instance IsGObject AesCbcCfbParams where
  typeGType :: AesCbcCfbParams -> JSM GType
typeGType AesCbcCfbParams
_ = JSM GType
gTypeAesCbcCfbParams
  {-# INLINE typeGType #-}

noAesCbcCfbParams :: Maybe AesCbcCfbParams
noAesCbcCfbParams :: Maybe AesCbcCfbParams
noAesCbcCfbParams = Maybe AesCbcCfbParams
forall a. Maybe a
Nothing
{-# INLINE noAesCbcCfbParams #-}

gTypeAesCbcCfbParams :: JSM GType
gTypeAesCbcCfbParams :: JSM GType
gTypeAesCbcCfbParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AesCbcCfbParams"

-- | Functions for this inteface are in "JSDOM.AesCtrParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AesCtrParams Mozilla AesCtrParams documentation>
newtype AesCtrParams = AesCtrParams { AesCtrParams -> JSVal
unAesCtrParams :: JSVal }

instance PToJSVal AesCtrParams where
  pToJSVal :: AesCtrParams -> JSVal
pToJSVal = AesCtrParams -> JSVal
unAesCtrParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal AesCtrParams where
  pFromJSVal :: JSVal -> AesCtrParams
pFromJSVal = JSVal -> AesCtrParams
AesCtrParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal AesCtrParams where
  toJSVal :: AesCtrParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AesCtrParams -> JSVal) -> AesCtrParams -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AesCtrParams -> JSVal
unAesCtrParams
  {-# INLINE toJSVal #-}

instance FromJSVal AesCtrParams where
  fromJSVal :: JSVal -> JSM (Maybe AesCtrParams)
fromJSVal JSVal
v = (JSVal -> AesCtrParams) -> Maybe JSVal -> Maybe AesCtrParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AesCtrParams
AesCtrParams (Maybe JSVal -> Maybe AesCtrParams)
-> JSM (Maybe JSVal) -> JSM (Maybe AesCtrParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AesCtrParams
fromJSValUnchecked = AesCtrParams -> JSM AesCtrParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AesCtrParams -> JSM AesCtrParams)
-> (JSVal -> AesCtrParams) -> JSVal -> JSM AesCtrParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AesCtrParams
AesCtrParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AesCtrParams where
  makeObject :: AesCtrParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AesCtrParams -> JSVal) -> AesCtrParams -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AesCtrParams -> JSVal
unAesCtrParams

instance IsCryptoAlgorithmParameters AesCtrParams
instance IsGObject AesCtrParams where
  typeGType :: AesCtrParams -> JSM GType
typeGType AesCtrParams
_ = JSM GType
gTypeAesCtrParams
  {-# INLINE typeGType #-}

noAesCtrParams :: Maybe AesCtrParams
noAesCtrParams :: Maybe AesCtrParams
noAesCtrParams = Maybe AesCtrParams
forall a. Maybe a
Nothing
{-# INLINE noAesCtrParams #-}

gTypeAesCtrParams :: JSM GType
gTypeAesCtrParams :: JSM GType
gTypeAesCtrParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AesCtrParams"

-- | Functions for this inteface are in "JSDOM.AesGcmParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AesGcmParams Mozilla AesGcmParams documentation>
newtype AesGcmParams = AesGcmParams { AesGcmParams -> JSVal
unAesGcmParams :: JSVal }

instance PToJSVal AesGcmParams where
  pToJSVal :: AesGcmParams -> JSVal
pToJSVal = AesGcmParams -> JSVal
unAesGcmParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal AesGcmParams where
  pFromJSVal :: JSVal -> AesGcmParams
pFromJSVal = JSVal -> AesGcmParams
AesGcmParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal AesGcmParams where
  toJSVal :: AesGcmParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AesGcmParams -> JSVal) -> AesGcmParams -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AesGcmParams -> JSVal
unAesGcmParams
  {-# INLINE toJSVal #-}

instance FromJSVal AesGcmParams where
  fromJSVal :: JSVal -> JSM (Maybe AesGcmParams)
fromJSVal JSVal
v = (JSVal -> AesGcmParams) -> Maybe JSVal -> Maybe AesGcmParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AesGcmParams
AesGcmParams (Maybe JSVal -> Maybe AesGcmParams)
-> JSM (Maybe JSVal) -> JSM (Maybe AesGcmParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AesGcmParams
fromJSValUnchecked = AesGcmParams -> JSM AesGcmParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AesGcmParams -> JSM AesGcmParams)
-> (JSVal -> AesGcmParams) -> JSVal -> JSM AesGcmParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AesGcmParams
AesGcmParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AesGcmParams where
  makeObject :: AesGcmParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AesGcmParams -> JSVal) -> AesGcmParams -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AesGcmParams -> JSVal
unAesGcmParams

instance IsCryptoAlgorithmParameters AesGcmParams
instance IsGObject AesGcmParams where
  typeGType :: AesGcmParams -> JSM GType
typeGType AesGcmParams
_ = JSM GType
gTypeAesGcmParams
  {-# INLINE typeGType #-}

noAesGcmParams :: Maybe AesGcmParams
noAesGcmParams :: Maybe AesGcmParams
noAesGcmParams = Maybe AesGcmParams
forall a. Maybe a
Nothing
{-# INLINE noAesGcmParams #-}

gTypeAesGcmParams :: JSM GType
gTypeAesGcmParams :: JSM GType
gTypeAesGcmParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AesGcmParams"

-- | Functions for this inteface are in "JSDOM.AesKeyParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AesKeyParams Mozilla AesKeyParams documentation>
newtype AesKeyParams = AesKeyParams { AesKeyParams -> JSVal
unAesKeyParams :: JSVal }

instance PToJSVal AesKeyParams where
  pToJSVal :: AesKeyParams -> JSVal
pToJSVal = AesKeyParams -> JSVal
unAesKeyParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal AesKeyParams where
  pFromJSVal :: JSVal -> AesKeyParams
pFromJSVal = JSVal -> AesKeyParams
AesKeyParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal AesKeyParams where
  toJSVal :: AesKeyParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AesKeyParams -> JSVal) -> AesKeyParams -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AesKeyParams -> JSVal
unAesKeyParams
  {-# INLINE toJSVal #-}

instance FromJSVal AesKeyParams where
  fromJSVal :: JSVal -> JSM (Maybe AesKeyParams)
fromJSVal JSVal
v = (JSVal -> AesKeyParams) -> Maybe JSVal -> Maybe AesKeyParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AesKeyParams
AesKeyParams (Maybe JSVal -> Maybe AesKeyParams)
-> JSM (Maybe JSVal) -> JSM (Maybe AesKeyParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AesKeyParams
fromJSValUnchecked = AesKeyParams -> JSM AesKeyParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AesKeyParams -> JSM AesKeyParams)
-> (JSVal -> AesKeyParams) -> JSVal -> JSM AesKeyParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AesKeyParams
AesKeyParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AesKeyParams where
  makeObject :: AesKeyParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AesKeyParams -> JSVal) -> AesKeyParams -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AesKeyParams -> JSVal
unAesKeyParams

instance IsCryptoAlgorithmParameters AesKeyParams
instance IsGObject AesKeyParams where
  typeGType :: AesKeyParams -> JSM GType
typeGType AesKeyParams
_ = JSM GType
gTypeAesKeyParams
  {-# INLINE typeGType #-}

noAesKeyParams :: Maybe AesKeyParams
noAesKeyParams :: Maybe AesKeyParams
noAesKeyParams = Maybe AesKeyParams
forall a. Maybe a
Nothing
{-# INLINE noAesKeyParams #-}

gTypeAesKeyParams :: JSM GType
gTypeAesKeyParams :: JSM GType
gTypeAesKeyParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AesKeyParams"

-- | Functions for this inteface are in "JSDOM.AnalyserNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AnalyserNode Mozilla AnalyserNode documentation>
newtype AnalyserNode = AnalyserNode { AnalyserNode -> JSVal
unAnalyserNode :: JSVal }

instance PToJSVal AnalyserNode where
  pToJSVal :: AnalyserNode -> JSVal
pToJSVal = AnalyserNode -> JSVal
unAnalyserNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal AnalyserNode where
  pFromJSVal :: JSVal -> AnalyserNode
pFromJSVal = JSVal -> AnalyserNode
AnalyserNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal AnalyserNode where
  toJSVal :: AnalyserNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AnalyserNode -> JSVal) -> AnalyserNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnalyserNode -> JSVal
unAnalyserNode
  {-# INLINE toJSVal #-}

instance FromJSVal AnalyserNode where
  fromJSVal :: JSVal -> JSM (Maybe AnalyserNode)
fromJSVal JSVal
v = (JSVal -> AnalyserNode) -> Maybe JSVal -> Maybe AnalyserNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AnalyserNode
AnalyserNode (Maybe JSVal -> Maybe AnalyserNode)
-> JSM (Maybe JSVal) -> JSM (Maybe AnalyserNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AnalyserNode
fromJSValUnchecked = AnalyserNode -> JSM AnalyserNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnalyserNode -> JSM AnalyserNode)
-> (JSVal -> AnalyserNode) -> JSVal -> JSM AnalyserNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AnalyserNode
AnalyserNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AnalyserNode where
  makeObject :: AnalyserNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AnalyserNode -> JSVal) -> AnalyserNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnalyserNode -> JSVal
unAnalyserNode

instance IsAudioNode AnalyserNode
instance IsEventTarget AnalyserNode
instance IsGObject AnalyserNode where
  typeGType :: AnalyserNode -> JSM GType
typeGType AnalyserNode
_ = JSM GType
gTypeAnalyserNode
  {-# INLINE typeGType #-}

noAnalyserNode :: Maybe AnalyserNode
noAnalyserNode :: Maybe AnalyserNode
noAnalyserNode = Maybe AnalyserNode
forall a. Maybe a
Nothing
{-# INLINE noAnalyserNode #-}

gTypeAnalyserNode :: JSM GType
gTypeAnalyserNode :: JSM GType
gTypeAnalyserNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AnalyserNode"

-- | Functions for this inteface are in "JSDOM.Animatable".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Animatable Mozilla Animatable documentation>
newtype Animatable = Animatable { Animatable -> JSVal
unAnimatable :: JSVal }

instance PToJSVal Animatable where
  pToJSVal :: Animatable -> JSVal
pToJSVal = Animatable -> JSVal
unAnimatable
  {-# INLINE pToJSVal #-}

instance PFromJSVal Animatable where
  pFromJSVal :: JSVal -> Animatable
pFromJSVal = JSVal -> Animatable
Animatable
  {-# INLINE pFromJSVal #-}

instance ToJSVal Animatable where
  toJSVal :: Animatable -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Animatable -> JSVal) -> Animatable -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Animatable -> JSVal
unAnimatable
  {-# INLINE toJSVal #-}

instance FromJSVal Animatable where
  fromJSVal :: JSVal -> JSM (Maybe Animatable)
fromJSVal JSVal
v = (JSVal -> Animatable) -> Maybe JSVal -> Maybe Animatable
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Animatable
Animatable (Maybe JSVal -> Maybe Animatable)
-> JSM (Maybe JSVal) -> JSM (Maybe Animatable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Animatable
fromJSValUnchecked = Animatable -> JSM Animatable
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Animatable -> JSM Animatable)
-> (JSVal -> Animatable) -> JSVal -> JSM Animatable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Animatable
Animatable
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Animatable where
  makeObject :: Animatable -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Animatable -> JSVal) -> Animatable -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Animatable -> JSVal
unAnimatable

class (IsGObject o) => IsAnimatable o
toAnimatable :: IsAnimatable o => o -> Animatable
toAnimatable :: forall o. IsAnimatable o => o -> Animatable
toAnimatable = JSVal -> Animatable
Animatable (JSVal -> Animatable) -> (o -> JSVal) -> o -> Animatable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsAnimatable Animatable
instance IsGObject Animatable where
  typeGType :: Animatable -> JSM GType
typeGType Animatable
_ = JSM GType
gTypeAnimatable
  {-# INLINE typeGType #-}

noAnimatable :: Maybe Animatable
noAnimatable :: Maybe Animatable
noAnimatable = Maybe Animatable
forall a. Maybe a
Nothing
{-# INLINE noAnimatable #-}

gTypeAnimatable :: JSM GType
gTypeAnimatable :: JSM GType
gTypeAnimatable = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Animatable"

-- | Functions for this inteface are in "JSDOM.Animation".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Animation Mozilla Animation documentation>
newtype Animation = Animation { Animation -> JSVal
unAnimation :: JSVal }

instance PToJSVal Animation where
  pToJSVal :: Animation -> JSVal
pToJSVal = Animation -> JSVal
unAnimation
  {-# INLINE pToJSVal #-}

instance PFromJSVal Animation where
  pFromJSVal :: JSVal -> Animation
pFromJSVal = JSVal -> Animation
Animation
  {-# INLINE pFromJSVal #-}

instance ToJSVal Animation where
  toJSVal :: Animation -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Animation -> JSVal) -> Animation -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Animation -> JSVal
unAnimation
  {-# INLINE toJSVal #-}

instance FromJSVal Animation where
  fromJSVal :: JSVal -> JSM (Maybe Animation)
fromJSVal JSVal
v = (JSVal -> Animation) -> Maybe JSVal -> Maybe Animation
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Animation
Animation (Maybe JSVal -> Maybe Animation)
-> JSM (Maybe JSVal) -> JSM (Maybe Animation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Animation
fromJSValUnchecked = Animation -> JSM Animation
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Animation -> JSM Animation)
-> (JSVal -> Animation) -> JSVal -> JSM Animation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Animation
Animation
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Animation where
  makeObject :: Animation -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Animation -> JSVal) -> Animation -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Animation -> JSVal
unAnimation

instance IsGObject Animation where
  typeGType :: Animation -> JSM GType
typeGType Animation
_ = JSM GType
gTypeAnimation
  {-# INLINE typeGType #-}

noAnimation :: Maybe Animation
noAnimation :: Maybe Animation
noAnimation = Maybe Animation
forall a. Maybe a
Nothing
{-# INLINE noAnimation #-}

gTypeAnimation :: JSM GType
gTypeAnimation :: JSM GType
gTypeAnimation = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Animation"

-- | Functions for this inteface are in "JSDOM.AnimationEffect".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AnimationEffect Mozilla AnimationEffect documentation>
newtype AnimationEffect = AnimationEffect { AnimationEffect -> JSVal
unAnimationEffect :: JSVal }

instance PToJSVal AnimationEffect where
  pToJSVal :: AnimationEffect -> JSVal
pToJSVal = AnimationEffect -> JSVal
unAnimationEffect
  {-# INLINE pToJSVal #-}

instance PFromJSVal AnimationEffect where
  pFromJSVal :: JSVal -> AnimationEffect
pFromJSVal = JSVal -> AnimationEffect
AnimationEffect
  {-# INLINE pFromJSVal #-}

instance ToJSVal AnimationEffect where
  toJSVal :: AnimationEffect -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AnimationEffect -> JSVal) -> AnimationEffect -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnimationEffect -> JSVal
unAnimationEffect
  {-# INLINE toJSVal #-}

instance FromJSVal AnimationEffect where
  fromJSVal :: JSVal -> JSM (Maybe AnimationEffect)
fromJSVal JSVal
v = (JSVal -> AnimationEffect) -> Maybe JSVal -> Maybe AnimationEffect
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AnimationEffect
AnimationEffect (Maybe JSVal -> Maybe AnimationEffect)
-> JSM (Maybe JSVal) -> JSM (Maybe AnimationEffect)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AnimationEffect
fromJSValUnchecked = AnimationEffect -> JSM AnimationEffect
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnimationEffect -> JSM AnimationEffect)
-> (JSVal -> AnimationEffect) -> JSVal -> JSM AnimationEffect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AnimationEffect
AnimationEffect
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AnimationEffect where
  makeObject :: AnimationEffect -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AnimationEffect -> JSVal) -> AnimationEffect -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnimationEffect -> JSVal
unAnimationEffect

class (IsGObject o) => IsAnimationEffect o
toAnimationEffect :: IsAnimationEffect o => o -> AnimationEffect
toAnimationEffect :: forall o. IsAnimationEffect o => o -> AnimationEffect
toAnimationEffect = JSVal -> AnimationEffect
AnimationEffect (JSVal -> AnimationEffect) -> (o -> JSVal) -> o -> AnimationEffect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsAnimationEffect AnimationEffect
instance IsGObject AnimationEffect where
  typeGType :: AnimationEffect -> JSM GType
typeGType AnimationEffect
_ = JSM GType
gTypeAnimationEffect
  {-# INLINE typeGType #-}

noAnimationEffect :: Maybe AnimationEffect
noAnimationEffect :: Maybe AnimationEffect
noAnimationEffect = Maybe AnimationEffect
forall a. Maybe a
Nothing
{-# INLINE noAnimationEffect #-}

gTypeAnimationEffect :: JSM GType
gTypeAnimationEffect :: JSM GType
gTypeAnimationEffect = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AnimationEffect"

-- | Functions for this inteface are in "JSDOM.AnimationEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AnimationEvent Mozilla AnimationEvent documentation>
newtype AnimationEvent = AnimationEvent { AnimationEvent -> JSVal
unAnimationEvent :: JSVal }

instance PToJSVal AnimationEvent where
  pToJSVal :: AnimationEvent -> JSVal
pToJSVal = AnimationEvent -> JSVal
unAnimationEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal AnimationEvent where
  pFromJSVal :: JSVal -> AnimationEvent
pFromJSVal = JSVal -> AnimationEvent
AnimationEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal AnimationEvent where
  toJSVal :: AnimationEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AnimationEvent -> JSVal) -> AnimationEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnimationEvent -> JSVal
unAnimationEvent
  {-# INLINE toJSVal #-}

instance FromJSVal AnimationEvent where
  fromJSVal :: JSVal -> JSM (Maybe AnimationEvent)
fromJSVal JSVal
v = (JSVal -> AnimationEvent) -> Maybe JSVal -> Maybe AnimationEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AnimationEvent
AnimationEvent (Maybe JSVal -> Maybe AnimationEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe AnimationEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AnimationEvent
fromJSValUnchecked = AnimationEvent -> JSM AnimationEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnimationEvent -> JSM AnimationEvent)
-> (JSVal -> AnimationEvent) -> JSVal -> JSM AnimationEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AnimationEvent
AnimationEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AnimationEvent where
  makeObject :: AnimationEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AnimationEvent -> JSVal) -> AnimationEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnimationEvent -> JSVal
unAnimationEvent

instance IsEvent AnimationEvent
instance IsGObject AnimationEvent where
  typeGType :: AnimationEvent -> JSM GType
typeGType AnimationEvent
_ = JSM GType
gTypeAnimationEvent
  {-# INLINE typeGType #-}

noAnimationEvent :: Maybe AnimationEvent
noAnimationEvent :: Maybe AnimationEvent
noAnimationEvent = Maybe AnimationEvent
forall a. Maybe a
Nothing
{-# INLINE noAnimationEvent #-}

gTypeAnimationEvent :: JSM GType
gTypeAnimationEvent :: JSM GType
gTypeAnimationEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AnimationEvent"

-- | Functions for this inteface are in "JSDOM.AnimationEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AnimationEventInit Mozilla AnimationEventInit documentation>
newtype AnimationEventInit = AnimationEventInit { AnimationEventInit -> JSVal
unAnimationEventInit :: JSVal }

instance PToJSVal AnimationEventInit where
  pToJSVal :: AnimationEventInit -> JSVal
pToJSVal = AnimationEventInit -> JSVal
unAnimationEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal AnimationEventInit where
  pFromJSVal :: JSVal -> AnimationEventInit
pFromJSVal = JSVal -> AnimationEventInit
AnimationEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal AnimationEventInit where
  toJSVal :: AnimationEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AnimationEventInit -> JSVal) -> AnimationEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnimationEventInit -> JSVal
unAnimationEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal AnimationEventInit where
  fromJSVal :: JSVal -> JSM (Maybe AnimationEventInit)
fromJSVal JSVal
v = (JSVal -> AnimationEventInit)
-> Maybe JSVal -> Maybe AnimationEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AnimationEventInit
AnimationEventInit (Maybe JSVal -> Maybe AnimationEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe AnimationEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AnimationEventInit
fromJSValUnchecked = AnimationEventInit -> JSM AnimationEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnimationEventInit -> JSM AnimationEventInit)
-> (JSVal -> AnimationEventInit) -> JSVal -> JSM AnimationEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AnimationEventInit
AnimationEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AnimationEventInit where
  makeObject :: AnimationEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AnimationEventInit -> JSVal)
-> AnimationEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnimationEventInit -> JSVal
unAnimationEventInit

instance IsEventInit AnimationEventInit
instance IsGObject AnimationEventInit where
  typeGType :: AnimationEventInit -> JSM GType
typeGType AnimationEventInit
_ = JSM GType
gTypeAnimationEventInit
  {-# INLINE typeGType #-}

noAnimationEventInit :: Maybe AnimationEventInit
noAnimationEventInit :: Maybe AnimationEventInit
noAnimationEventInit = Maybe AnimationEventInit
forall a. Maybe a
Nothing
{-# INLINE noAnimationEventInit #-}

gTypeAnimationEventInit :: JSM GType
gTypeAnimationEventInit :: JSM GType
gTypeAnimationEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AnimationEventInit"

-- | Functions for this inteface are in "JSDOM.AnimationTimeline".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AnimationTimeline Mozilla AnimationTimeline documentation>
newtype AnimationTimeline = AnimationTimeline { AnimationTimeline -> JSVal
unAnimationTimeline :: JSVal }

instance PToJSVal AnimationTimeline where
  pToJSVal :: AnimationTimeline -> JSVal
pToJSVal = AnimationTimeline -> JSVal
unAnimationTimeline
  {-# INLINE pToJSVal #-}

instance PFromJSVal AnimationTimeline where
  pFromJSVal :: JSVal -> AnimationTimeline
pFromJSVal = JSVal -> AnimationTimeline
AnimationTimeline
  {-# INLINE pFromJSVal #-}

instance ToJSVal AnimationTimeline where
  toJSVal :: AnimationTimeline -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AnimationTimeline -> JSVal) -> AnimationTimeline -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnimationTimeline -> JSVal
unAnimationTimeline
  {-# INLINE toJSVal #-}

instance FromJSVal AnimationTimeline where
  fromJSVal :: JSVal -> JSM (Maybe AnimationTimeline)
fromJSVal JSVal
v = (JSVal -> AnimationTimeline)
-> Maybe JSVal -> Maybe AnimationTimeline
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AnimationTimeline
AnimationTimeline (Maybe JSVal -> Maybe AnimationTimeline)
-> JSM (Maybe JSVal) -> JSM (Maybe AnimationTimeline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AnimationTimeline
fromJSValUnchecked = AnimationTimeline -> JSM AnimationTimeline
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnimationTimeline -> JSM AnimationTimeline)
-> (JSVal -> AnimationTimeline) -> JSVal -> JSM AnimationTimeline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AnimationTimeline
AnimationTimeline
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AnimationTimeline where
  makeObject :: AnimationTimeline -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AnimationTimeline -> JSVal) -> AnimationTimeline -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnimationTimeline -> JSVal
unAnimationTimeline

class (IsGObject o) => IsAnimationTimeline o
toAnimationTimeline :: IsAnimationTimeline o => o -> AnimationTimeline
toAnimationTimeline :: forall o. IsAnimationTimeline o => o -> AnimationTimeline
toAnimationTimeline = JSVal -> AnimationTimeline
AnimationTimeline (JSVal -> AnimationTimeline)
-> (o -> JSVal) -> o -> AnimationTimeline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsAnimationTimeline AnimationTimeline
instance IsGObject AnimationTimeline where
  typeGType :: AnimationTimeline -> JSM GType
typeGType AnimationTimeline
_ = JSM GType
gTypeAnimationTimeline
  {-# INLINE typeGType #-}

noAnimationTimeline :: Maybe AnimationTimeline
noAnimationTimeline :: Maybe AnimationTimeline
noAnimationTimeline = Maybe AnimationTimeline
forall a. Maybe a
Nothing
{-# INLINE noAnimationTimeline #-}

gTypeAnimationTimeline :: JSM GType
gTypeAnimationTimeline :: JSM GType
gTypeAnimationTimeline = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AnimationTimeline"

-- | Functions for this inteface are in "JSDOM.ApplePayError".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayError Mozilla ApplePayError documentation>
newtype ApplePayError = ApplePayError { ApplePayError -> JSVal
unApplePayError :: JSVal }

instance PToJSVal ApplePayError where
  pToJSVal :: ApplePayError -> JSVal
pToJSVal = ApplePayError -> JSVal
unApplePayError
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayError where
  pFromJSVal :: JSVal -> ApplePayError
pFromJSVal = JSVal -> ApplePayError
ApplePayError
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayError where
  toJSVal :: ApplePayError -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayError -> JSVal) -> ApplePayError -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayError -> JSVal
unApplePayError
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayError where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayError)
fromJSVal JSVal
v = (JSVal -> ApplePayError) -> Maybe JSVal -> Maybe ApplePayError
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayError
ApplePayError (Maybe JSVal -> Maybe ApplePayError)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayError
fromJSValUnchecked = ApplePayError -> JSM ApplePayError
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayError -> JSM ApplePayError)
-> (JSVal -> ApplePayError) -> JSVal -> JSM ApplePayError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayError
ApplePayError
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayError where
  makeObject :: ApplePayError -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayError -> JSVal) -> ApplePayError -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayError -> JSVal
unApplePayError

instance IsGObject ApplePayError where
  typeGType :: ApplePayError -> JSM GType
typeGType ApplePayError
_ = JSM GType
gTypeApplePayError
  {-# INLINE typeGType #-}

noApplePayError :: Maybe ApplePayError
noApplePayError :: Maybe ApplePayError
noApplePayError = Maybe ApplePayError
forall a. Maybe a
Nothing
{-# INLINE noApplePayError #-}

gTypeApplePayError :: JSM GType
gTypeApplePayError :: JSM GType
gTypeApplePayError = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayError"

-- | Functions for this inteface are in "JSDOM.ApplePayLineItem".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayLineItem Mozilla ApplePayLineItem documentation>
newtype ApplePayLineItem = ApplePayLineItem { ApplePayLineItem -> JSVal
unApplePayLineItem :: JSVal }

instance PToJSVal ApplePayLineItem where
  pToJSVal :: ApplePayLineItem -> JSVal
pToJSVal = ApplePayLineItem -> JSVal
unApplePayLineItem
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayLineItem where
  pFromJSVal :: JSVal -> ApplePayLineItem
pFromJSVal = JSVal -> ApplePayLineItem
ApplePayLineItem
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayLineItem where
  toJSVal :: ApplePayLineItem -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayLineItem -> JSVal) -> ApplePayLineItem -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayLineItem -> JSVal
unApplePayLineItem
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayLineItem where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayLineItem)
fromJSVal JSVal
v = (JSVal -> ApplePayLineItem)
-> Maybe JSVal -> Maybe ApplePayLineItem
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayLineItem
ApplePayLineItem (Maybe JSVal -> Maybe ApplePayLineItem)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayLineItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayLineItem
fromJSValUnchecked = ApplePayLineItem -> JSM ApplePayLineItem
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayLineItem -> JSM ApplePayLineItem)
-> (JSVal -> ApplePayLineItem) -> JSVal -> JSM ApplePayLineItem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayLineItem
ApplePayLineItem
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayLineItem where
  makeObject :: ApplePayLineItem -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayLineItem -> JSVal) -> ApplePayLineItem -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayLineItem -> JSVal
unApplePayLineItem

instance IsGObject ApplePayLineItem where
  typeGType :: ApplePayLineItem -> JSM GType
typeGType ApplePayLineItem
_ = JSM GType
gTypeApplePayLineItem
  {-# INLINE typeGType #-}

noApplePayLineItem :: Maybe ApplePayLineItem
noApplePayLineItem :: Maybe ApplePayLineItem
noApplePayLineItem = Maybe ApplePayLineItem
forall a. Maybe a
Nothing
{-# INLINE noApplePayLineItem #-}

gTypeApplePayLineItem :: JSM GType
gTypeApplePayLineItem :: JSM GType
gTypeApplePayLineItem = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayLineItem"

-- | Functions for this inteface are in "JSDOM.ApplePayPayment".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayPayment Mozilla ApplePayPayment documentation>
newtype ApplePayPayment = ApplePayPayment { ApplePayPayment -> JSVal
unApplePayPayment :: JSVal }

instance PToJSVal ApplePayPayment where
  pToJSVal :: ApplePayPayment -> JSVal
pToJSVal = ApplePayPayment -> JSVal
unApplePayPayment
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayPayment where
  pFromJSVal :: JSVal -> ApplePayPayment
pFromJSVal = JSVal -> ApplePayPayment
ApplePayPayment
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayPayment where
  toJSVal :: ApplePayPayment -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayPayment -> JSVal) -> ApplePayPayment -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPayment -> JSVal
unApplePayPayment
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayPayment where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayPayment)
fromJSVal JSVal
v = (JSVal -> ApplePayPayment) -> Maybe JSVal -> Maybe ApplePayPayment
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayPayment
ApplePayPayment (Maybe JSVal -> Maybe ApplePayPayment)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayPayment)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayPayment
fromJSValUnchecked = ApplePayPayment -> JSM ApplePayPayment
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPayment -> JSM ApplePayPayment)
-> (JSVal -> ApplePayPayment) -> JSVal -> JSM ApplePayPayment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayPayment
ApplePayPayment
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayPayment where
  makeObject :: ApplePayPayment -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayPayment -> JSVal) -> ApplePayPayment -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPayment -> JSVal
unApplePayPayment

instance IsGObject ApplePayPayment where
  typeGType :: ApplePayPayment -> JSM GType
typeGType ApplePayPayment
_ = JSM GType
gTypeApplePayPayment
  {-# INLINE typeGType #-}

noApplePayPayment :: Maybe ApplePayPayment
noApplePayPayment :: Maybe ApplePayPayment
noApplePayPayment = Maybe ApplePayPayment
forall a. Maybe a
Nothing
{-# INLINE noApplePayPayment #-}

gTypeApplePayPayment :: JSM GType
gTypeApplePayPayment :: JSM GType
gTypeApplePayPayment = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayPayment"

-- | Functions for this inteface are in "JSDOM.ApplePayPaymentAuthorizationResult".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayPaymentAuthorizationResult Mozilla ApplePayPaymentAuthorizationResult documentation>
newtype ApplePayPaymentAuthorizationResult = ApplePayPaymentAuthorizationResult { ApplePayPaymentAuthorizationResult -> JSVal
unApplePayPaymentAuthorizationResult :: JSVal }

instance PToJSVal ApplePayPaymentAuthorizationResult where
  pToJSVal :: ApplePayPaymentAuthorizationResult -> JSVal
pToJSVal = ApplePayPaymentAuthorizationResult -> JSVal
unApplePayPaymentAuthorizationResult
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayPaymentAuthorizationResult where
  pFromJSVal :: JSVal -> ApplePayPaymentAuthorizationResult
pFromJSVal = JSVal -> ApplePayPaymentAuthorizationResult
ApplePayPaymentAuthorizationResult
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayPaymentAuthorizationResult where
  toJSVal :: ApplePayPaymentAuthorizationResult -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayPaymentAuthorizationResult -> JSVal)
-> ApplePayPaymentAuthorizationResult
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentAuthorizationResult -> JSVal
unApplePayPaymentAuthorizationResult
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayPaymentAuthorizationResult where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayPaymentAuthorizationResult)
fromJSVal JSVal
v = (JSVal -> ApplePayPaymentAuthorizationResult)
-> Maybe JSVal -> Maybe ApplePayPaymentAuthorizationResult
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayPaymentAuthorizationResult
ApplePayPaymentAuthorizationResult (Maybe JSVal -> Maybe ApplePayPaymentAuthorizationResult)
-> JSM (Maybe JSVal)
-> JSM (Maybe ApplePayPaymentAuthorizationResult)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayPaymentAuthorizationResult
fromJSValUnchecked = ApplePayPaymentAuthorizationResult
-> JSM ApplePayPaymentAuthorizationResult
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentAuthorizationResult
 -> JSM ApplePayPaymentAuthorizationResult)
-> (JSVal -> ApplePayPaymentAuthorizationResult)
-> JSVal
-> JSM ApplePayPaymentAuthorizationResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayPaymentAuthorizationResult
ApplePayPaymentAuthorizationResult
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayPaymentAuthorizationResult where
  makeObject :: ApplePayPaymentAuthorizationResult -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayPaymentAuthorizationResult -> JSVal)
-> ApplePayPaymentAuthorizationResult
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentAuthorizationResult -> JSVal
unApplePayPaymentAuthorizationResult

instance IsGObject ApplePayPaymentAuthorizationResult where
  typeGType :: ApplePayPaymentAuthorizationResult -> JSM GType
typeGType ApplePayPaymentAuthorizationResult
_ = JSM GType
gTypeApplePayPaymentAuthorizationResult
  {-# INLINE typeGType #-}

noApplePayPaymentAuthorizationResult :: Maybe ApplePayPaymentAuthorizationResult
noApplePayPaymentAuthorizationResult :: Maybe ApplePayPaymentAuthorizationResult
noApplePayPaymentAuthorizationResult = Maybe ApplePayPaymentAuthorizationResult
forall a. Maybe a
Nothing
{-# INLINE noApplePayPaymentAuthorizationResult #-}

gTypeApplePayPaymentAuthorizationResult :: JSM GType
gTypeApplePayPaymentAuthorizationResult :: JSM GType
gTypeApplePayPaymentAuthorizationResult = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayPaymentAuthorizationResult"

-- | Functions for this inteface are in "JSDOM.ApplePayPaymentAuthorizedEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayPaymentAuthorizedEvent Mozilla ApplePayPaymentAuthorizedEvent documentation>
newtype ApplePayPaymentAuthorizedEvent = ApplePayPaymentAuthorizedEvent { ApplePayPaymentAuthorizedEvent -> JSVal
unApplePayPaymentAuthorizedEvent :: JSVal }

instance PToJSVal ApplePayPaymentAuthorizedEvent where
  pToJSVal :: ApplePayPaymentAuthorizedEvent -> JSVal
pToJSVal = ApplePayPaymentAuthorizedEvent -> JSVal
unApplePayPaymentAuthorizedEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayPaymentAuthorizedEvent where
  pFromJSVal :: JSVal -> ApplePayPaymentAuthorizedEvent
pFromJSVal = JSVal -> ApplePayPaymentAuthorizedEvent
ApplePayPaymentAuthorizedEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayPaymentAuthorizedEvent where
  toJSVal :: ApplePayPaymentAuthorizedEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayPaymentAuthorizedEvent -> JSVal)
-> ApplePayPaymentAuthorizedEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentAuthorizedEvent -> JSVal
unApplePayPaymentAuthorizedEvent
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayPaymentAuthorizedEvent where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayPaymentAuthorizedEvent)
fromJSVal JSVal
v = (JSVal -> ApplePayPaymentAuthorizedEvent)
-> Maybe JSVal -> Maybe ApplePayPaymentAuthorizedEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayPaymentAuthorizedEvent
ApplePayPaymentAuthorizedEvent (Maybe JSVal -> Maybe ApplePayPaymentAuthorizedEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayPaymentAuthorizedEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayPaymentAuthorizedEvent
fromJSValUnchecked = ApplePayPaymentAuthorizedEvent
-> JSM ApplePayPaymentAuthorizedEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentAuthorizedEvent
 -> JSM ApplePayPaymentAuthorizedEvent)
-> (JSVal -> ApplePayPaymentAuthorizedEvent)
-> JSVal
-> JSM ApplePayPaymentAuthorizedEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayPaymentAuthorizedEvent
ApplePayPaymentAuthorizedEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayPaymentAuthorizedEvent where
  makeObject :: ApplePayPaymentAuthorizedEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayPaymentAuthorizedEvent -> JSVal)
-> ApplePayPaymentAuthorizedEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentAuthorizedEvent -> JSVal
unApplePayPaymentAuthorizedEvent

instance IsEvent ApplePayPaymentAuthorizedEvent
instance IsGObject ApplePayPaymentAuthorizedEvent where
  typeGType :: ApplePayPaymentAuthorizedEvent -> JSM GType
typeGType ApplePayPaymentAuthorizedEvent
_ = JSM GType
gTypeApplePayPaymentAuthorizedEvent
  {-# INLINE typeGType #-}

noApplePayPaymentAuthorizedEvent :: Maybe ApplePayPaymentAuthorizedEvent
noApplePayPaymentAuthorizedEvent :: Maybe ApplePayPaymentAuthorizedEvent
noApplePayPaymentAuthorizedEvent = Maybe ApplePayPaymentAuthorizedEvent
forall a. Maybe a
Nothing
{-# INLINE noApplePayPaymentAuthorizedEvent #-}

gTypeApplePayPaymentAuthorizedEvent :: JSM GType
gTypeApplePayPaymentAuthorizedEvent :: JSM GType
gTypeApplePayPaymentAuthorizedEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayPaymentAuthorizedEvent"

-- | Functions for this inteface are in "JSDOM.ApplePayPaymentContact".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayPaymentContact Mozilla ApplePayPaymentContact documentation>
newtype ApplePayPaymentContact = ApplePayPaymentContact { ApplePayPaymentContact -> JSVal
unApplePayPaymentContact :: JSVal }

instance PToJSVal ApplePayPaymentContact where
  pToJSVal :: ApplePayPaymentContact -> JSVal
pToJSVal = ApplePayPaymentContact -> JSVal
unApplePayPaymentContact
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayPaymentContact where
  pFromJSVal :: JSVal -> ApplePayPaymentContact
pFromJSVal = JSVal -> ApplePayPaymentContact
ApplePayPaymentContact
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayPaymentContact where
  toJSVal :: ApplePayPaymentContact -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayPaymentContact -> JSVal)
-> ApplePayPaymentContact
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentContact -> JSVal
unApplePayPaymentContact
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayPaymentContact where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayPaymentContact)
fromJSVal JSVal
v = (JSVal -> ApplePayPaymentContact)
-> Maybe JSVal -> Maybe ApplePayPaymentContact
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayPaymentContact
ApplePayPaymentContact (Maybe JSVal -> Maybe ApplePayPaymentContact)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayPaymentContact)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayPaymentContact
fromJSValUnchecked = ApplePayPaymentContact -> JSM ApplePayPaymentContact
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentContact -> JSM ApplePayPaymentContact)
-> (JSVal -> ApplePayPaymentContact)
-> JSVal
-> JSM ApplePayPaymentContact
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayPaymentContact
ApplePayPaymentContact
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayPaymentContact where
  makeObject :: ApplePayPaymentContact -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayPaymentContact -> JSVal)
-> ApplePayPaymentContact
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentContact -> JSVal
unApplePayPaymentContact

instance IsGObject ApplePayPaymentContact where
  typeGType :: ApplePayPaymentContact -> JSM GType
typeGType ApplePayPaymentContact
_ = JSM GType
gTypeApplePayPaymentContact
  {-# INLINE typeGType #-}

noApplePayPaymentContact :: Maybe ApplePayPaymentContact
noApplePayPaymentContact :: Maybe ApplePayPaymentContact
noApplePayPaymentContact = Maybe ApplePayPaymentContact
forall a. Maybe a
Nothing
{-# INLINE noApplePayPaymentContact #-}

gTypeApplePayPaymentContact :: JSM GType
gTypeApplePayPaymentContact :: JSM GType
gTypeApplePayPaymentContact = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayPaymentContact"

-- | Functions for this inteface are in "JSDOM.ApplePayPaymentMethod".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayPaymentMethod Mozilla ApplePayPaymentMethod documentation>
newtype ApplePayPaymentMethod = ApplePayPaymentMethod { ApplePayPaymentMethod -> JSVal
unApplePayPaymentMethod :: JSVal }

instance PToJSVal ApplePayPaymentMethod where
  pToJSVal :: ApplePayPaymentMethod -> JSVal
pToJSVal = ApplePayPaymentMethod -> JSVal
unApplePayPaymentMethod
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayPaymentMethod where
  pFromJSVal :: JSVal -> ApplePayPaymentMethod
pFromJSVal = JSVal -> ApplePayPaymentMethod
ApplePayPaymentMethod
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayPaymentMethod where
  toJSVal :: ApplePayPaymentMethod -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayPaymentMethod -> JSVal)
-> ApplePayPaymentMethod
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentMethod -> JSVal
unApplePayPaymentMethod
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayPaymentMethod where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayPaymentMethod)
fromJSVal JSVal
v = (JSVal -> ApplePayPaymentMethod)
-> Maybe JSVal -> Maybe ApplePayPaymentMethod
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayPaymentMethod
ApplePayPaymentMethod (Maybe JSVal -> Maybe ApplePayPaymentMethod)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayPaymentMethod)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayPaymentMethod
fromJSValUnchecked = ApplePayPaymentMethod -> JSM ApplePayPaymentMethod
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentMethod -> JSM ApplePayPaymentMethod)
-> (JSVal -> ApplePayPaymentMethod)
-> JSVal
-> JSM ApplePayPaymentMethod
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayPaymentMethod
ApplePayPaymentMethod
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayPaymentMethod where
  makeObject :: ApplePayPaymentMethod -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayPaymentMethod -> JSVal)
-> ApplePayPaymentMethod
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentMethod -> JSVal
unApplePayPaymentMethod

instance IsGObject ApplePayPaymentMethod where
  typeGType :: ApplePayPaymentMethod -> JSM GType
typeGType ApplePayPaymentMethod
_ = JSM GType
gTypeApplePayPaymentMethod
  {-# INLINE typeGType #-}

noApplePayPaymentMethod :: Maybe ApplePayPaymentMethod
noApplePayPaymentMethod :: Maybe ApplePayPaymentMethod
noApplePayPaymentMethod = Maybe ApplePayPaymentMethod
forall a. Maybe a
Nothing
{-# INLINE noApplePayPaymentMethod #-}

gTypeApplePayPaymentMethod :: JSM GType
gTypeApplePayPaymentMethod :: JSM GType
gTypeApplePayPaymentMethod = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayPaymentMethod"

-- | Functions for this inteface are in "JSDOM.ApplePayPaymentMethodSelectedEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayPaymentMethodSelectedEvent Mozilla ApplePayPaymentMethodSelectedEvent documentation>
newtype ApplePayPaymentMethodSelectedEvent = ApplePayPaymentMethodSelectedEvent { ApplePayPaymentMethodSelectedEvent -> JSVal
unApplePayPaymentMethodSelectedEvent :: JSVal }

instance PToJSVal ApplePayPaymentMethodSelectedEvent where
  pToJSVal :: ApplePayPaymentMethodSelectedEvent -> JSVal
pToJSVal = ApplePayPaymentMethodSelectedEvent -> JSVal
unApplePayPaymentMethodSelectedEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayPaymentMethodSelectedEvent where
  pFromJSVal :: JSVal -> ApplePayPaymentMethodSelectedEvent
pFromJSVal = JSVal -> ApplePayPaymentMethodSelectedEvent
ApplePayPaymentMethodSelectedEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayPaymentMethodSelectedEvent where
  toJSVal :: ApplePayPaymentMethodSelectedEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayPaymentMethodSelectedEvent -> JSVal)
-> ApplePayPaymentMethodSelectedEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentMethodSelectedEvent -> JSVal
unApplePayPaymentMethodSelectedEvent
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayPaymentMethodSelectedEvent where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayPaymentMethodSelectedEvent)
fromJSVal JSVal
v = (JSVal -> ApplePayPaymentMethodSelectedEvent)
-> Maybe JSVal -> Maybe ApplePayPaymentMethodSelectedEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayPaymentMethodSelectedEvent
ApplePayPaymentMethodSelectedEvent (Maybe JSVal -> Maybe ApplePayPaymentMethodSelectedEvent)
-> JSM (Maybe JSVal)
-> JSM (Maybe ApplePayPaymentMethodSelectedEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayPaymentMethodSelectedEvent
fromJSValUnchecked = ApplePayPaymentMethodSelectedEvent
-> JSM ApplePayPaymentMethodSelectedEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentMethodSelectedEvent
 -> JSM ApplePayPaymentMethodSelectedEvent)
-> (JSVal -> ApplePayPaymentMethodSelectedEvent)
-> JSVal
-> JSM ApplePayPaymentMethodSelectedEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayPaymentMethodSelectedEvent
ApplePayPaymentMethodSelectedEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayPaymentMethodSelectedEvent where
  makeObject :: ApplePayPaymentMethodSelectedEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayPaymentMethodSelectedEvent -> JSVal)
-> ApplePayPaymentMethodSelectedEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentMethodSelectedEvent -> JSVal
unApplePayPaymentMethodSelectedEvent

instance IsEvent ApplePayPaymentMethodSelectedEvent
instance IsGObject ApplePayPaymentMethodSelectedEvent where
  typeGType :: ApplePayPaymentMethodSelectedEvent -> JSM GType
typeGType ApplePayPaymentMethodSelectedEvent
_ = JSM GType
gTypeApplePayPaymentMethodSelectedEvent
  {-# INLINE typeGType #-}

noApplePayPaymentMethodSelectedEvent :: Maybe ApplePayPaymentMethodSelectedEvent
noApplePayPaymentMethodSelectedEvent :: Maybe ApplePayPaymentMethodSelectedEvent
noApplePayPaymentMethodSelectedEvent = Maybe ApplePayPaymentMethodSelectedEvent
forall a. Maybe a
Nothing
{-# INLINE noApplePayPaymentMethodSelectedEvent #-}

gTypeApplePayPaymentMethodSelectedEvent :: JSM GType
gTypeApplePayPaymentMethodSelectedEvent :: JSM GType
gTypeApplePayPaymentMethodSelectedEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayPaymentMethodSelectedEvent"

-- | Functions for this inteface are in "JSDOM.ApplePayPaymentMethodUpdate".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayPaymentMethodUpdate Mozilla ApplePayPaymentMethodUpdate documentation>
newtype ApplePayPaymentMethodUpdate = ApplePayPaymentMethodUpdate { ApplePayPaymentMethodUpdate -> JSVal
unApplePayPaymentMethodUpdate :: JSVal }

instance PToJSVal ApplePayPaymentMethodUpdate where
  pToJSVal :: ApplePayPaymentMethodUpdate -> JSVal
pToJSVal = ApplePayPaymentMethodUpdate -> JSVal
unApplePayPaymentMethodUpdate
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayPaymentMethodUpdate where
  pFromJSVal :: JSVal -> ApplePayPaymentMethodUpdate
pFromJSVal = JSVal -> ApplePayPaymentMethodUpdate
ApplePayPaymentMethodUpdate
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayPaymentMethodUpdate where
  toJSVal :: ApplePayPaymentMethodUpdate -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayPaymentMethodUpdate -> JSVal)
-> ApplePayPaymentMethodUpdate
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentMethodUpdate -> JSVal
unApplePayPaymentMethodUpdate
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayPaymentMethodUpdate where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayPaymentMethodUpdate)
fromJSVal JSVal
v = (JSVal -> ApplePayPaymentMethodUpdate)
-> Maybe JSVal -> Maybe ApplePayPaymentMethodUpdate
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayPaymentMethodUpdate
ApplePayPaymentMethodUpdate (Maybe JSVal -> Maybe ApplePayPaymentMethodUpdate)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayPaymentMethodUpdate)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayPaymentMethodUpdate
fromJSValUnchecked = ApplePayPaymentMethodUpdate -> JSM ApplePayPaymentMethodUpdate
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentMethodUpdate -> JSM ApplePayPaymentMethodUpdate)
-> (JSVal -> ApplePayPaymentMethodUpdate)
-> JSVal
-> JSM ApplePayPaymentMethodUpdate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayPaymentMethodUpdate
ApplePayPaymentMethodUpdate
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayPaymentMethodUpdate where
  makeObject :: ApplePayPaymentMethodUpdate -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayPaymentMethodUpdate -> JSVal)
-> ApplePayPaymentMethodUpdate
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentMethodUpdate -> JSVal
unApplePayPaymentMethodUpdate

instance IsGObject ApplePayPaymentMethodUpdate where
  typeGType :: ApplePayPaymentMethodUpdate -> JSM GType
typeGType ApplePayPaymentMethodUpdate
_ = JSM GType
gTypeApplePayPaymentMethodUpdate
  {-# INLINE typeGType #-}

noApplePayPaymentMethodUpdate :: Maybe ApplePayPaymentMethodUpdate
noApplePayPaymentMethodUpdate :: Maybe ApplePayPaymentMethodUpdate
noApplePayPaymentMethodUpdate = Maybe ApplePayPaymentMethodUpdate
forall a. Maybe a
Nothing
{-# INLINE noApplePayPaymentMethodUpdate #-}

gTypeApplePayPaymentMethodUpdate :: JSM GType
gTypeApplePayPaymentMethodUpdate :: JSM GType
gTypeApplePayPaymentMethodUpdate = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayPaymentMethodUpdate"

-- | Functions for this inteface are in "JSDOM.ApplePayPaymentPass".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayPaymentPass Mozilla ApplePayPaymentPass documentation>
newtype ApplePayPaymentPass = ApplePayPaymentPass { ApplePayPaymentPass -> JSVal
unApplePayPaymentPass :: JSVal }

instance PToJSVal ApplePayPaymentPass where
  pToJSVal :: ApplePayPaymentPass -> JSVal
pToJSVal = ApplePayPaymentPass -> JSVal
unApplePayPaymentPass
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayPaymentPass where
  pFromJSVal :: JSVal -> ApplePayPaymentPass
pFromJSVal = JSVal -> ApplePayPaymentPass
ApplePayPaymentPass
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayPaymentPass where
  toJSVal :: ApplePayPaymentPass -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayPaymentPass -> JSVal)
-> ApplePayPaymentPass
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentPass -> JSVal
unApplePayPaymentPass
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayPaymentPass where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayPaymentPass)
fromJSVal JSVal
v = (JSVal -> ApplePayPaymentPass)
-> Maybe JSVal -> Maybe ApplePayPaymentPass
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayPaymentPass
ApplePayPaymentPass (Maybe JSVal -> Maybe ApplePayPaymentPass)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayPaymentPass)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayPaymentPass
fromJSValUnchecked = ApplePayPaymentPass -> JSM ApplePayPaymentPass
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentPass -> JSM ApplePayPaymentPass)
-> (JSVal -> ApplePayPaymentPass)
-> JSVal
-> JSM ApplePayPaymentPass
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayPaymentPass
ApplePayPaymentPass
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayPaymentPass where
  makeObject :: ApplePayPaymentPass -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayPaymentPass -> JSVal)
-> ApplePayPaymentPass
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentPass -> JSVal
unApplePayPaymentPass

instance IsGObject ApplePayPaymentPass where
  typeGType :: ApplePayPaymentPass -> JSM GType
typeGType ApplePayPaymentPass
_ = JSM GType
gTypeApplePayPaymentPass
  {-# INLINE typeGType #-}

noApplePayPaymentPass :: Maybe ApplePayPaymentPass
noApplePayPaymentPass :: Maybe ApplePayPaymentPass
noApplePayPaymentPass = Maybe ApplePayPaymentPass
forall a. Maybe a
Nothing
{-# INLINE noApplePayPaymentPass #-}

gTypeApplePayPaymentPass :: JSM GType
gTypeApplePayPaymentPass :: JSM GType
gTypeApplePayPaymentPass = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayPaymentPass"

-- | Functions for this inteface are in "JSDOM.ApplePayPaymentRequest".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayPaymentRequest Mozilla ApplePayPaymentRequest documentation>
newtype ApplePayPaymentRequest = ApplePayPaymentRequest { ApplePayPaymentRequest -> JSVal
unApplePayPaymentRequest :: JSVal }

instance PToJSVal ApplePayPaymentRequest where
  pToJSVal :: ApplePayPaymentRequest -> JSVal
pToJSVal = ApplePayPaymentRequest -> JSVal
unApplePayPaymentRequest
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayPaymentRequest where
  pFromJSVal :: JSVal -> ApplePayPaymentRequest
pFromJSVal = JSVal -> ApplePayPaymentRequest
ApplePayPaymentRequest
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayPaymentRequest where
  toJSVal :: ApplePayPaymentRequest -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayPaymentRequest -> JSVal)
-> ApplePayPaymentRequest
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentRequest -> JSVal
unApplePayPaymentRequest
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayPaymentRequest where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayPaymentRequest)
fromJSVal JSVal
v = (JSVal -> ApplePayPaymentRequest)
-> Maybe JSVal -> Maybe ApplePayPaymentRequest
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayPaymentRequest
ApplePayPaymentRequest (Maybe JSVal -> Maybe ApplePayPaymentRequest)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayPaymentRequest)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayPaymentRequest
fromJSValUnchecked = ApplePayPaymentRequest -> JSM ApplePayPaymentRequest
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentRequest -> JSM ApplePayPaymentRequest)
-> (JSVal -> ApplePayPaymentRequest)
-> JSVal
-> JSM ApplePayPaymentRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayPaymentRequest
ApplePayPaymentRequest
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayPaymentRequest where
  makeObject :: ApplePayPaymentRequest -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayPaymentRequest -> JSVal)
-> ApplePayPaymentRequest
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentRequest -> JSVal
unApplePayPaymentRequest

instance IsGObject ApplePayPaymentRequest where
  typeGType :: ApplePayPaymentRequest -> JSM GType
typeGType ApplePayPaymentRequest
_ = JSM GType
gTypeApplePayPaymentRequest
  {-# INLINE typeGType #-}

noApplePayPaymentRequest :: Maybe ApplePayPaymentRequest
noApplePayPaymentRequest :: Maybe ApplePayPaymentRequest
noApplePayPaymentRequest = Maybe ApplePayPaymentRequest
forall a. Maybe a
Nothing
{-# INLINE noApplePayPaymentRequest #-}

gTypeApplePayPaymentRequest :: JSM GType
gTypeApplePayPaymentRequest :: JSM GType
gTypeApplePayPaymentRequest = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayPaymentRequest"

-- | Functions for this inteface are in "JSDOM.ApplePayPaymentToken".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayPaymentToken Mozilla ApplePayPaymentToken documentation>
newtype ApplePayPaymentToken = ApplePayPaymentToken { ApplePayPaymentToken -> JSVal
unApplePayPaymentToken :: JSVal }

instance PToJSVal ApplePayPaymentToken where
  pToJSVal :: ApplePayPaymentToken -> JSVal
pToJSVal = ApplePayPaymentToken -> JSVal
unApplePayPaymentToken
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayPaymentToken where
  pFromJSVal :: JSVal -> ApplePayPaymentToken
pFromJSVal = JSVal -> ApplePayPaymentToken
ApplePayPaymentToken
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayPaymentToken where
  toJSVal :: ApplePayPaymentToken -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayPaymentToken -> JSVal)
-> ApplePayPaymentToken
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentToken -> JSVal
unApplePayPaymentToken
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayPaymentToken where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayPaymentToken)
fromJSVal JSVal
v = (JSVal -> ApplePayPaymentToken)
-> Maybe JSVal -> Maybe ApplePayPaymentToken
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayPaymentToken
ApplePayPaymentToken (Maybe JSVal -> Maybe ApplePayPaymentToken)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayPaymentToken)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayPaymentToken
fromJSValUnchecked = ApplePayPaymentToken -> JSM ApplePayPaymentToken
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentToken -> JSM ApplePayPaymentToken)
-> (JSVal -> ApplePayPaymentToken)
-> JSVal
-> JSM ApplePayPaymentToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayPaymentToken
ApplePayPaymentToken
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayPaymentToken where
  makeObject :: ApplePayPaymentToken -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayPaymentToken -> JSVal)
-> ApplePayPaymentToken
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayPaymentToken -> JSVal
unApplePayPaymentToken

instance IsGObject ApplePayPaymentToken where
  typeGType :: ApplePayPaymentToken -> JSM GType
typeGType ApplePayPaymentToken
_ = JSM GType
gTypeApplePayPaymentToken
  {-# INLINE typeGType #-}

noApplePayPaymentToken :: Maybe ApplePayPaymentToken
noApplePayPaymentToken :: Maybe ApplePayPaymentToken
noApplePayPaymentToken = Maybe ApplePayPaymentToken
forall a. Maybe a
Nothing
{-# INLINE noApplePayPaymentToken #-}

gTypeApplePayPaymentToken :: JSM GType
gTypeApplePayPaymentToken :: JSM GType
gTypeApplePayPaymentToken = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayPaymentToken"

-- | Functions for this inteface are in "JSDOM.ApplePaySession".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePaySession Mozilla ApplePaySession documentation>
newtype ApplePaySession = ApplePaySession { ApplePaySession -> JSVal
unApplePaySession :: JSVal }

instance PToJSVal ApplePaySession where
  pToJSVal :: ApplePaySession -> JSVal
pToJSVal = ApplePaySession -> JSVal
unApplePaySession
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePaySession where
  pFromJSVal :: JSVal -> ApplePaySession
pFromJSVal = JSVal -> ApplePaySession
ApplePaySession
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePaySession where
  toJSVal :: ApplePaySession -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePaySession -> JSVal) -> ApplePaySession -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePaySession -> JSVal
unApplePaySession
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePaySession where
  fromJSVal :: JSVal -> JSM (Maybe ApplePaySession)
fromJSVal JSVal
v = (JSVal -> ApplePaySession) -> Maybe JSVal -> Maybe ApplePaySession
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePaySession
ApplePaySession (Maybe JSVal -> Maybe ApplePaySession)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePaySession)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePaySession
fromJSValUnchecked = ApplePaySession -> JSM ApplePaySession
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePaySession -> JSM ApplePaySession)
-> (JSVal -> ApplePaySession) -> JSVal -> JSM ApplePaySession
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePaySession
ApplePaySession
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePaySession where
  makeObject :: ApplePaySession -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePaySession -> JSVal) -> ApplePaySession -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePaySession -> JSVal
unApplePaySession

instance IsEventTarget ApplePaySession
instance IsGObject ApplePaySession where
  typeGType :: ApplePaySession -> JSM GType
typeGType ApplePaySession
_ = JSM GType
gTypeApplePaySession
  {-# INLINE typeGType #-}

noApplePaySession :: Maybe ApplePaySession
noApplePaySession :: Maybe ApplePaySession
noApplePaySession = Maybe ApplePaySession
forall a. Maybe a
Nothing
{-# INLINE noApplePaySession #-}

gTypeApplePaySession :: JSM GType
gTypeApplePaySession :: JSM GType
gTypeApplePaySession = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePaySession"

-- | Functions for this inteface are in "JSDOM.ApplePayShippingContactSelectedEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayShippingContactSelectedEvent Mozilla ApplePayShippingContactSelectedEvent documentation>
newtype ApplePayShippingContactSelectedEvent = ApplePayShippingContactSelectedEvent { ApplePayShippingContactSelectedEvent -> JSVal
unApplePayShippingContactSelectedEvent :: JSVal }

instance PToJSVal ApplePayShippingContactSelectedEvent where
  pToJSVal :: ApplePayShippingContactSelectedEvent -> JSVal
pToJSVal = ApplePayShippingContactSelectedEvent -> JSVal
unApplePayShippingContactSelectedEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayShippingContactSelectedEvent where
  pFromJSVal :: JSVal -> ApplePayShippingContactSelectedEvent
pFromJSVal = JSVal -> ApplePayShippingContactSelectedEvent
ApplePayShippingContactSelectedEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayShippingContactSelectedEvent where
  toJSVal :: ApplePayShippingContactSelectedEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayShippingContactSelectedEvent -> JSVal)
-> ApplePayShippingContactSelectedEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayShippingContactSelectedEvent -> JSVal
unApplePayShippingContactSelectedEvent
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayShippingContactSelectedEvent where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayShippingContactSelectedEvent)
fromJSVal JSVal
v = (JSVal -> ApplePayShippingContactSelectedEvent)
-> Maybe JSVal -> Maybe ApplePayShippingContactSelectedEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayShippingContactSelectedEvent
ApplePayShippingContactSelectedEvent (Maybe JSVal -> Maybe ApplePayShippingContactSelectedEvent)
-> JSM (Maybe JSVal)
-> JSM (Maybe ApplePayShippingContactSelectedEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayShippingContactSelectedEvent
fromJSValUnchecked = ApplePayShippingContactSelectedEvent
-> JSM ApplePayShippingContactSelectedEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayShippingContactSelectedEvent
 -> JSM ApplePayShippingContactSelectedEvent)
-> (JSVal -> ApplePayShippingContactSelectedEvent)
-> JSVal
-> JSM ApplePayShippingContactSelectedEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayShippingContactSelectedEvent
ApplePayShippingContactSelectedEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayShippingContactSelectedEvent where
  makeObject :: ApplePayShippingContactSelectedEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayShippingContactSelectedEvent -> JSVal)
-> ApplePayShippingContactSelectedEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayShippingContactSelectedEvent -> JSVal
unApplePayShippingContactSelectedEvent

instance IsEvent ApplePayShippingContactSelectedEvent
instance IsGObject ApplePayShippingContactSelectedEvent where
  typeGType :: ApplePayShippingContactSelectedEvent -> JSM GType
typeGType ApplePayShippingContactSelectedEvent
_ = JSM GType
gTypeApplePayShippingContactSelectedEvent
  {-# INLINE typeGType #-}

noApplePayShippingContactSelectedEvent :: Maybe ApplePayShippingContactSelectedEvent
noApplePayShippingContactSelectedEvent :: Maybe ApplePayShippingContactSelectedEvent
noApplePayShippingContactSelectedEvent = Maybe ApplePayShippingContactSelectedEvent
forall a. Maybe a
Nothing
{-# INLINE noApplePayShippingContactSelectedEvent #-}

gTypeApplePayShippingContactSelectedEvent :: JSM GType
gTypeApplePayShippingContactSelectedEvent :: JSM GType
gTypeApplePayShippingContactSelectedEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayShippingContactSelectedEvent"

-- | Functions for this inteface are in "JSDOM.ApplePayShippingContactUpdate".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayShippingContactUpdate Mozilla ApplePayShippingContactUpdate documentation>
newtype ApplePayShippingContactUpdate = ApplePayShippingContactUpdate { ApplePayShippingContactUpdate -> JSVal
unApplePayShippingContactUpdate :: JSVal }

instance PToJSVal ApplePayShippingContactUpdate where
  pToJSVal :: ApplePayShippingContactUpdate -> JSVal
pToJSVal = ApplePayShippingContactUpdate -> JSVal
unApplePayShippingContactUpdate
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayShippingContactUpdate where
  pFromJSVal :: JSVal -> ApplePayShippingContactUpdate
pFromJSVal = JSVal -> ApplePayShippingContactUpdate
ApplePayShippingContactUpdate
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayShippingContactUpdate where
  toJSVal :: ApplePayShippingContactUpdate -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayShippingContactUpdate -> JSVal)
-> ApplePayShippingContactUpdate
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayShippingContactUpdate -> JSVal
unApplePayShippingContactUpdate
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayShippingContactUpdate where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayShippingContactUpdate)
fromJSVal JSVal
v = (JSVal -> ApplePayShippingContactUpdate)
-> Maybe JSVal -> Maybe ApplePayShippingContactUpdate
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayShippingContactUpdate
ApplePayShippingContactUpdate (Maybe JSVal -> Maybe ApplePayShippingContactUpdate)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayShippingContactUpdate)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayShippingContactUpdate
fromJSValUnchecked = ApplePayShippingContactUpdate -> JSM ApplePayShippingContactUpdate
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayShippingContactUpdate
 -> JSM ApplePayShippingContactUpdate)
-> (JSVal -> ApplePayShippingContactUpdate)
-> JSVal
-> JSM ApplePayShippingContactUpdate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayShippingContactUpdate
ApplePayShippingContactUpdate
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayShippingContactUpdate where
  makeObject :: ApplePayShippingContactUpdate -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayShippingContactUpdate -> JSVal)
-> ApplePayShippingContactUpdate
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayShippingContactUpdate -> JSVal
unApplePayShippingContactUpdate

instance IsGObject ApplePayShippingContactUpdate where
  typeGType :: ApplePayShippingContactUpdate -> JSM GType
typeGType ApplePayShippingContactUpdate
_ = JSM GType
gTypeApplePayShippingContactUpdate
  {-# INLINE typeGType #-}

noApplePayShippingContactUpdate :: Maybe ApplePayShippingContactUpdate
noApplePayShippingContactUpdate :: Maybe ApplePayShippingContactUpdate
noApplePayShippingContactUpdate = Maybe ApplePayShippingContactUpdate
forall a. Maybe a
Nothing
{-# INLINE noApplePayShippingContactUpdate #-}

gTypeApplePayShippingContactUpdate :: JSM GType
gTypeApplePayShippingContactUpdate :: JSM GType
gTypeApplePayShippingContactUpdate = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayShippingContactUpdate"

-- | Functions for this inteface are in "JSDOM.ApplePayShippingMethod".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayShippingMethod Mozilla ApplePayShippingMethod documentation>
newtype ApplePayShippingMethod = ApplePayShippingMethod { ApplePayShippingMethod -> JSVal
unApplePayShippingMethod :: JSVal }

instance PToJSVal ApplePayShippingMethod where
  pToJSVal :: ApplePayShippingMethod -> JSVal
pToJSVal = ApplePayShippingMethod -> JSVal
unApplePayShippingMethod
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayShippingMethod where
  pFromJSVal :: JSVal -> ApplePayShippingMethod
pFromJSVal = JSVal -> ApplePayShippingMethod
ApplePayShippingMethod
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayShippingMethod where
  toJSVal :: ApplePayShippingMethod -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayShippingMethod -> JSVal)
-> ApplePayShippingMethod
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayShippingMethod -> JSVal
unApplePayShippingMethod
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayShippingMethod where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayShippingMethod)
fromJSVal JSVal
v = (JSVal -> ApplePayShippingMethod)
-> Maybe JSVal -> Maybe ApplePayShippingMethod
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayShippingMethod
ApplePayShippingMethod (Maybe JSVal -> Maybe ApplePayShippingMethod)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayShippingMethod)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayShippingMethod
fromJSValUnchecked = ApplePayShippingMethod -> JSM ApplePayShippingMethod
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayShippingMethod -> JSM ApplePayShippingMethod)
-> (JSVal -> ApplePayShippingMethod)
-> JSVal
-> JSM ApplePayShippingMethod
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayShippingMethod
ApplePayShippingMethod
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayShippingMethod where
  makeObject :: ApplePayShippingMethod -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayShippingMethod -> JSVal)
-> ApplePayShippingMethod
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayShippingMethod -> JSVal
unApplePayShippingMethod

instance IsGObject ApplePayShippingMethod where
  typeGType :: ApplePayShippingMethod -> JSM GType
typeGType ApplePayShippingMethod
_ = JSM GType
gTypeApplePayShippingMethod
  {-# INLINE typeGType #-}

noApplePayShippingMethod :: Maybe ApplePayShippingMethod
noApplePayShippingMethod :: Maybe ApplePayShippingMethod
noApplePayShippingMethod = Maybe ApplePayShippingMethod
forall a. Maybe a
Nothing
{-# INLINE noApplePayShippingMethod #-}

gTypeApplePayShippingMethod :: JSM GType
gTypeApplePayShippingMethod :: JSM GType
gTypeApplePayShippingMethod = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayShippingMethod"

-- | Functions for this inteface are in "JSDOM.ApplePayShippingMethodSelectedEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayShippingMethodSelectedEvent Mozilla ApplePayShippingMethodSelectedEvent documentation>
newtype ApplePayShippingMethodSelectedEvent = ApplePayShippingMethodSelectedEvent { ApplePayShippingMethodSelectedEvent -> JSVal
unApplePayShippingMethodSelectedEvent :: JSVal }

instance PToJSVal ApplePayShippingMethodSelectedEvent where
  pToJSVal :: ApplePayShippingMethodSelectedEvent -> JSVal
pToJSVal = ApplePayShippingMethodSelectedEvent -> JSVal
unApplePayShippingMethodSelectedEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayShippingMethodSelectedEvent where
  pFromJSVal :: JSVal -> ApplePayShippingMethodSelectedEvent
pFromJSVal = JSVal -> ApplePayShippingMethodSelectedEvent
ApplePayShippingMethodSelectedEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayShippingMethodSelectedEvent where
  toJSVal :: ApplePayShippingMethodSelectedEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayShippingMethodSelectedEvent -> JSVal)
-> ApplePayShippingMethodSelectedEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayShippingMethodSelectedEvent -> JSVal
unApplePayShippingMethodSelectedEvent
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayShippingMethodSelectedEvent where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayShippingMethodSelectedEvent)
fromJSVal JSVal
v = (JSVal -> ApplePayShippingMethodSelectedEvent)
-> Maybe JSVal -> Maybe ApplePayShippingMethodSelectedEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayShippingMethodSelectedEvent
ApplePayShippingMethodSelectedEvent (Maybe JSVal -> Maybe ApplePayShippingMethodSelectedEvent)
-> JSM (Maybe JSVal)
-> JSM (Maybe ApplePayShippingMethodSelectedEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayShippingMethodSelectedEvent
fromJSValUnchecked = ApplePayShippingMethodSelectedEvent
-> JSM ApplePayShippingMethodSelectedEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayShippingMethodSelectedEvent
 -> JSM ApplePayShippingMethodSelectedEvent)
-> (JSVal -> ApplePayShippingMethodSelectedEvent)
-> JSVal
-> JSM ApplePayShippingMethodSelectedEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayShippingMethodSelectedEvent
ApplePayShippingMethodSelectedEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayShippingMethodSelectedEvent where
  makeObject :: ApplePayShippingMethodSelectedEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayShippingMethodSelectedEvent -> JSVal)
-> ApplePayShippingMethodSelectedEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayShippingMethodSelectedEvent -> JSVal
unApplePayShippingMethodSelectedEvent

instance IsEvent ApplePayShippingMethodSelectedEvent
instance IsGObject ApplePayShippingMethodSelectedEvent where
  typeGType :: ApplePayShippingMethodSelectedEvent -> JSM GType
typeGType ApplePayShippingMethodSelectedEvent
_ = JSM GType
gTypeApplePayShippingMethodSelectedEvent
  {-# INLINE typeGType #-}

noApplePayShippingMethodSelectedEvent :: Maybe ApplePayShippingMethodSelectedEvent
noApplePayShippingMethodSelectedEvent :: Maybe ApplePayShippingMethodSelectedEvent
noApplePayShippingMethodSelectedEvent = Maybe ApplePayShippingMethodSelectedEvent
forall a. Maybe a
Nothing
{-# INLINE noApplePayShippingMethodSelectedEvent #-}

gTypeApplePayShippingMethodSelectedEvent :: JSM GType
gTypeApplePayShippingMethodSelectedEvent :: JSM GType
gTypeApplePayShippingMethodSelectedEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayShippingMethodSelectedEvent"

-- | Functions for this inteface are in "JSDOM.ApplePayShippingMethodUpdate".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayShippingMethodUpdate Mozilla ApplePayShippingMethodUpdate documentation>
newtype ApplePayShippingMethodUpdate = ApplePayShippingMethodUpdate { ApplePayShippingMethodUpdate -> JSVal
unApplePayShippingMethodUpdate :: JSVal }

instance PToJSVal ApplePayShippingMethodUpdate where
  pToJSVal :: ApplePayShippingMethodUpdate -> JSVal
pToJSVal = ApplePayShippingMethodUpdate -> JSVal
unApplePayShippingMethodUpdate
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayShippingMethodUpdate where
  pFromJSVal :: JSVal -> ApplePayShippingMethodUpdate
pFromJSVal = JSVal -> ApplePayShippingMethodUpdate
ApplePayShippingMethodUpdate
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayShippingMethodUpdate where
  toJSVal :: ApplePayShippingMethodUpdate -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayShippingMethodUpdate -> JSVal)
-> ApplePayShippingMethodUpdate
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayShippingMethodUpdate -> JSVal
unApplePayShippingMethodUpdate
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayShippingMethodUpdate where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayShippingMethodUpdate)
fromJSVal JSVal
v = (JSVal -> ApplePayShippingMethodUpdate)
-> Maybe JSVal -> Maybe ApplePayShippingMethodUpdate
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayShippingMethodUpdate
ApplePayShippingMethodUpdate (Maybe JSVal -> Maybe ApplePayShippingMethodUpdate)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayShippingMethodUpdate)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayShippingMethodUpdate
fromJSValUnchecked = ApplePayShippingMethodUpdate -> JSM ApplePayShippingMethodUpdate
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayShippingMethodUpdate -> JSM ApplePayShippingMethodUpdate)
-> (JSVal -> ApplePayShippingMethodUpdate)
-> JSVal
-> JSM ApplePayShippingMethodUpdate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayShippingMethodUpdate
ApplePayShippingMethodUpdate
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayShippingMethodUpdate where
  makeObject :: ApplePayShippingMethodUpdate -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayShippingMethodUpdate -> JSVal)
-> ApplePayShippingMethodUpdate
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayShippingMethodUpdate -> JSVal
unApplePayShippingMethodUpdate

instance IsGObject ApplePayShippingMethodUpdate where
  typeGType :: ApplePayShippingMethodUpdate -> JSM GType
typeGType ApplePayShippingMethodUpdate
_ = JSM GType
gTypeApplePayShippingMethodUpdate
  {-# INLINE typeGType #-}

noApplePayShippingMethodUpdate :: Maybe ApplePayShippingMethodUpdate
noApplePayShippingMethodUpdate :: Maybe ApplePayShippingMethodUpdate
noApplePayShippingMethodUpdate = Maybe ApplePayShippingMethodUpdate
forall a. Maybe a
Nothing
{-# INLINE noApplePayShippingMethodUpdate #-}

gTypeApplePayShippingMethodUpdate :: JSM GType
gTypeApplePayShippingMethodUpdate :: JSM GType
gTypeApplePayShippingMethodUpdate = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayShippingMethodUpdate"

-- | Functions for this inteface are in "JSDOM.ApplePayValidateMerchantEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplePayValidateMerchantEvent Mozilla ApplePayValidateMerchantEvent documentation>
newtype ApplePayValidateMerchantEvent = ApplePayValidateMerchantEvent { ApplePayValidateMerchantEvent -> JSVal
unApplePayValidateMerchantEvent :: JSVal }

instance PToJSVal ApplePayValidateMerchantEvent where
  pToJSVal :: ApplePayValidateMerchantEvent -> JSVal
pToJSVal = ApplePayValidateMerchantEvent -> JSVal
unApplePayValidateMerchantEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplePayValidateMerchantEvent where
  pFromJSVal :: JSVal -> ApplePayValidateMerchantEvent
pFromJSVal = JSVal -> ApplePayValidateMerchantEvent
ApplePayValidateMerchantEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplePayValidateMerchantEvent where
  toJSVal :: ApplePayValidateMerchantEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplePayValidateMerchantEvent -> JSVal)
-> ApplePayValidateMerchantEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayValidateMerchantEvent -> JSVal
unApplePayValidateMerchantEvent
  {-# INLINE toJSVal #-}

instance FromJSVal ApplePayValidateMerchantEvent where
  fromJSVal :: JSVal -> JSM (Maybe ApplePayValidateMerchantEvent)
fromJSVal JSVal
v = (JSVal -> ApplePayValidateMerchantEvent)
-> Maybe JSVal -> Maybe ApplePayValidateMerchantEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplePayValidateMerchantEvent
ApplePayValidateMerchantEvent (Maybe JSVal -> Maybe ApplePayValidateMerchantEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplePayValidateMerchantEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplePayValidateMerchantEvent
fromJSValUnchecked = ApplePayValidateMerchantEvent -> JSM ApplePayValidateMerchantEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayValidateMerchantEvent
 -> JSM ApplePayValidateMerchantEvent)
-> (JSVal -> ApplePayValidateMerchantEvent)
-> JSVal
-> JSM ApplePayValidateMerchantEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplePayValidateMerchantEvent
ApplePayValidateMerchantEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplePayValidateMerchantEvent where
  makeObject :: ApplePayValidateMerchantEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplePayValidateMerchantEvent -> JSVal)
-> ApplePayValidateMerchantEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplePayValidateMerchantEvent -> JSVal
unApplePayValidateMerchantEvent

instance IsEvent ApplePayValidateMerchantEvent
instance IsGObject ApplePayValidateMerchantEvent where
  typeGType :: ApplePayValidateMerchantEvent -> JSM GType
typeGType ApplePayValidateMerchantEvent
_ = JSM GType
gTypeApplePayValidateMerchantEvent
  {-# INLINE typeGType #-}

noApplePayValidateMerchantEvent :: Maybe ApplePayValidateMerchantEvent
noApplePayValidateMerchantEvent :: Maybe ApplePayValidateMerchantEvent
noApplePayValidateMerchantEvent = Maybe ApplePayValidateMerchantEvent
forall a. Maybe a
Nothing
{-# INLINE noApplePayValidateMerchantEvent #-}

gTypeApplePayValidateMerchantEvent :: JSM GType
gTypeApplePayValidateMerchantEvent :: JSM GType
gTypeApplePayValidateMerchantEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplePayValidateMerchantEvent"

-- | Functions for this inteface are in "JSDOM.ApplicationCache".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ApplicationCache Mozilla ApplicationCache documentation>
newtype ApplicationCache = ApplicationCache { ApplicationCache -> JSVal
unApplicationCache :: JSVal }

instance PToJSVal ApplicationCache where
  pToJSVal :: ApplicationCache -> JSVal
pToJSVal = ApplicationCache -> JSVal
unApplicationCache
  {-# INLINE pToJSVal #-}

instance PFromJSVal ApplicationCache where
  pFromJSVal :: JSVal -> ApplicationCache
pFromJSVal = JSVal -> ApplicationCache
ApplicationCache
  {-# INLINE pFromJSVal #-}

instance ToJSVal ApplicationCache where
  toJSVal :: ApplicationCache -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ApplicationCache -> JSVal) -> ApplicationCache -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplicationCache -> JSVal
unApplicationCache
  {-# INLINE toJSVal #-}

instance FromJSVal ApplicationCache where
  fromJSVal :: JSVal -> JSM (Maybe ApplicationCache)
fromJSVal JSVal
v = (JSVal -> ApplicationCache)
-> Maybe JSVal -> Maybe ApplicationCache
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ApplicationCache
ApplicationCache (Maybe JSVal -> Maybe ApplicationCache)
-> JSM (Maybe JSVal) -> JSM (Maybe ApplicationCache)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ApplicationCache
fromJSValUnchecked = ApplicationCache -> JSM ApplicationCache
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplicationCache -> JSM ApplicationCache)
-> (JSVal -> ApplicationCache) -> JSVal -> JSM ApplicationCache
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ApplicationCache
ApplicationCache
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ApplicationCache where
  makeObject :: ApplicationCache -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ApplicationCache -> JSVal) -> ApplicationCache -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ApplicationCache -> JSVal
unApplicationCache

instance IsEventTarget ApplicationCache
instance IsGObject ApplicationCache where
  typeGType :: ApplicationCache -> JSM GType
typeGType ApplicationCache
_ = JSM GType
gTypeApplicationCache
  {-# INLINE typeGType #-}

noApplicationCache :: Maybe ApplicationCache
noApplicationCache :: Maybe ApplicationCache
noApplicationCache = Maybe ApplicationCache
forall a. Maybe a
Nothing
{-# INLINE noApplicationCache #-}

gTypeApplicationCache :: JSM GType
gTypeApplicationCache :: JSM GType
gTypeApplicationCache = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ApplicationCache"

-- | Functions for this inteface are in "JSDOM.AssignedNodesOptions".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AssignedNodesOptions Mozilla AssignedNodesOptions documentation>
newtype AssignedNodesOptions = AssignedNodesOptions { AssignedNodesOptions -> JSVal
unAssignedNodesOptions :: JSVal }

instance PToJSVal AssignedNodesOptions where
  pToJSVal :: AssignedNodesOptions -> JSVal
pToJSVal = AssignedNodesOptions -> JSVal
unAssignedNodesOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal AssignedNodesOptions where
  pFromJSVal :: JSVal -> AssignedNodesOptions
pFromJSVal = JSVal -> AssignedNodesOptions
AssignedNodesOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal AssignedNodesOptions where
  toJSVal :: AssignedNodesOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AssignedNodesOptions -> JSVal)
-> AssignedNodesOptions
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AssignedNodesOptions -> JSVal
unAssignedNodesOptions
  {-# INLINE toJSVal #-}

instance FromJSVal AssignedNodesOptions where
  fromJSVal :: JSVal -> JSM (Maybe AssignedNodesOptions)
fromJSVal JSVal
v = (JSVal -> AssignedNodesOptions)
-> Maybe JSVal -> Maybe AssignedNodesOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AssignedNodesOptions
AssignedNodesOptions (Maybe JSVal -> Maybe AssignedNodesOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe AssignedNodesOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AssignedNodesOptions
fromJSValUnchecked = AssignedNodesOptions -> JSM AssignedNodesOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AssignedNodesOptions -> JSM AssignedNodesOptions)
-> (JSVal -> AssignedNodesOptions)
-> JSVal
-> JSM AssignedNodesOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AssignedNodesOptions
AssignedNodesOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AssignedNodesOptions where
  makeObject :: AssignedNodesOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AssignedNodesOptions -> JSVal)
-> AssignedNodesOptions
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AssignedNodesOptions -> JSVal
unAssignedNodesOptions

instance IsGObject AssignedNodesOptions where
  typeGType :: AssignedNodesOptions -> JSM GType
typeGType AssignedNodesOptions
_ = JSM GType
gTypeAssignedNodesOptions
  {-# INLINE typeGType #-}

noAssignedNodesOptions :: Maybe AssignedNodesOptions
noAssignedNodesOptions :: Maybe AssignedNodesOptions
noAssignedNodesOptions = Maybe AssignedNodesOptions
forall a. Maybe a
Nothing
{-# INLINE noAssignedNodesOptions #-}

gTypeAssignedNodesOptions :: JSM GType
gTypeAssignedNodesOptions :: JSM GType
gTypeAssignedNodesOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AssignedNodesOptions"

-- | Functions for this inteface are in "JSDOM.Attr".
-- Base interface functions are in:
--
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Attr Mozilla Attr documentation>
newtype Attr = Attr { Attr -> JSVal
unAttr :: JSVal }

instance PToJSVal Attr where
  pToJSVal :: Attr -> JSVal
pToJSVal = Attr -> JSVal
unAttr
  {-# INLINE pToJSVal #-}

instance PFromJSVal Attr where
  pFromJSVal :: JSVal -> Attr
pFromJSVal = JSVal -> Attr
Attr
  {-# INLINE pFromJSVal #-}

instance ToJSVal Attr where
  toJSVal :: Attr -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Attr -> JSVal) -> Attr -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> JSVal
unAttr
  {-# INLINE toJSVal #-}

instance FromJSVal Attr where
  fromJSVal :: JSVal -> JSM (Maybe Attr)
fromJSVal JSVal
v = (JSVal -> Attr) -> Maybe JSVal -> Maybe Attr
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Attr
Attr (Maybe JSVal -> Maybe Attr)
-> JSM (Maybe JSVal) -> JSM (Maybe Attr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Attr
fromJSValUnchecked = Attr -> JSM Attr
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Attr -> JSM Attr) -> (JSVal -> Attr) -> JSVal -> JSM Attr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Attr
Attr
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Attr where
  makeObject :: Attr -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Attr -> JSVal) -> Attr -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> JSVal
unAttr

instance IsNode Attr
instance IsEventTarget Attr
instance IsGObject Attr where
  typeGType :: Attr -> JSM GType
typeGType Attr
_ = JSM GType
gTypeAttr
  {-# INLINE typeGType #-}

noAttr :: Maybe Attr
noAttr :: Maybe Attr
noAttr = Maybe Attr
forall a. Maybe a
Nothing
{-# INLINE noAttr #-}

gTypeAttr :: JSM GType
gTypeAttr :: JSM GType
gTypeAttr = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Attr"

-- | Functions for this inteface are in "JSDOM.AudioBuffer".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AudioBuffer Mozilla AudioBuffer documentation>
newtype AudioBuffer = AudioBuffer { AudioBuffer -> JSVal
unAudioBuffer :: JSVal }

instance PToJSVal AudioBuffer where
  pToJSVal :: AudioBuffer -> JSVal
pToJSVal = AudioBuffer -> JSVal
unAudioBuffer
  {-# INLINE pToJSVal #-}

instance PFromJSVal AudioBuffer where
  pFromJSVal :: JSVal -> AudioBuffer
pFromJSVal = JSVal -> AudioBuffer
AudioBuffer
  {-# INLINE pFromJSVal #-}

instance ToJSVal AudioBuffer where
  toJSVal :: AudioBuffer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AudioBuffer -> JSVal) -> AudioBuffer -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioBuffer -> JSVal
unAudioBuffer
  {-# INLINE toJSVal #-}

instance FromJSVal AudioBuffer where
  fromJSVal :: JSVal -> JSM (Maybe AudioBuffer)
fromJSVal JSVal
v = (JSVal -> AudioBuffer) -> Maybe JSVal -> Maybe AudioBuffer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AudioBuffer
AudioBuffer (Maybe JSVal -> Maybe AudioBuffer)
-> JSM (Maybe JSVal) -> JSM (Maybe AudioBuffer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AudioBuffer
fromJSValUnchecked = AudioBuffer -> JSM AudioBuffer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioBuffer -> JSM AudioBuffer)
-> (JSVal -> AudioBuffer) -> JSVal -> JSM AudioBuffer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AudioBuffer
AudioBuffer
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AudioBuffer where
  makeObject :: AudioBuffer -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AudioBuffer -> JSVal) -> AudioBuffer -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioBuffer -> JSVal
unAudioBuffer

instance IsGObject AudioBuffer where
  typeGType :: AudioBuffer -> JSM GType
typeGType AudioBuffer
_ = JSM GType
gTypeAudioBuffer
  {-# INLINE typeGType #-}

noAudioBuffer :: Maybe AudioBuffer
noAudioBuffer :: Maybe AudioBuffer
noAudioBuffer = Maybe AudioBuffer
forall a. Maybe a
Nothing
{-# INLINE noAudioBuffer #-}

gTypeAudioBuffer :: JSM GType
gTypeAudioBuffer :: JSM GType
gTypeAudioBuffer = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AudioBuffer"

-- | Functions for this inteface are in "JSDOM.AudioBufferSourceNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AudioBufferSourceNode Mozilla AudioBufferSourceNode documentation>
newtype AudioBufferSourceNode = AudioBufferSourceNode { AudioBufferSourceNode -> JSVal
unAudioBufferSourceNode :: JSVal }

instance PToJSVal AudioBufferSourceNode where
  pToJSVal :: AudioBufferSourceNode -> JSVal
pToJSVal = AudioBufferSourceNode -> JSVal
unAudioBufferSourceNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal AudioBufferSourceNode where
  pFromJSVal :: JSVal -> AudioBufferSourceNode
pFromJSVal = JSVal -> AudioBufferSourceNode
AudioBufferSourceNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal AudioBufferSourceNode where
  toJSVal :: AudioBufferSourceNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AudioBufferSourceNode -> JSVal)
-> AudioBufferSourceNode
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioBufferSourceNode -> JSVal
unAudioBufferSourceNode
  {-# INLINE toJSVal #-}

instance FromJSVal AudioBufferSourceNode where
  fromJSVal :: JSVal -> JSM (Maybe AudioBufferSourceNode)
fromJSVal JSVal
v = (JSVal -> AudioBufferSourceNode)
-> Maybe JSVal -> Maybe AudioBufferSourceNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AudioBufferSourceNode
AudioBufferSourceNode (Maybe JSVal -> Maybe AudioBufferSourceNode)
-> JSM (Maybe JSVal) -> JSM (Maybe AudioBufferSourceNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AudioBufferSourceNode
fromJSValUnchecked = AudioBufferSourceNode -> JSM AudioBufferSourceNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioBufferSourceNode -> JSM AudioBufferSourceNode)
-> (JSVal -> AudioBufferSourceNode)
-> JSVal
-> JSM AudioBufferSourceNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AudioBufferSourceNode
AudioBufferSourceNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AudioBufferSourceNode where
  makeObject :: AudioBufferSourceNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AudioBufferSourceNode -> JSVal)
-> AudioBufferSourceNode
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioBufferSourceNode -> JSVal
unAudioBufferSourceNode

instance IsAudioNode AudioBufferSourceNode
instance IsEventTarget AudioBufferSourceNode
instance IsGObject AudioBufferSourceNode where
  typeGType :: AudioBufferSourceNode -> JSM GType
typeGType AudioBufferSourceNode
_ = JSM GType
gTypeAudioBufferSourceNode
  {-# INLINE typeGType #-}

noAudioBufferSourceNode :: Maybe AudioBufferSourceNode
noAudioBufferSourceNode :: Maybe AudioBufferSourceNode
noAudioBufferSourceNode = Maybe AudioBufferSourceNode
forall a. Maybe a
Nothing
{-# INLINE noAudioBufferSourceNode #-}

gTypeAudioBufferSourceNode :: JSM GType
gTypeAudioBufferSourceNode :: JSM GType
gTypeAudioBufferSourceNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AudioBufferSourceNode"

-- | Functions for this inteface are in "JSDOM.AudioContext".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AudioContext Mozilla AudioContext documentation>
newtype AudioContext = AudioContext { AudioContext -> JSVal
unAudioContext :: JSVal }

instance PToJSVal AudioContext where
  pToJSVal :: AudioContext -> JSVal
pToJSVal = AudioContext -> JSVal
unAudioContext
  {-# INLINE pToJSVal #-}

instance PFromJSVal AudioContext where
  pFromJSVal :: JSVal -> AudioContext
pFromJSVal = JSVal -> AudioContext
AudioContext
  {-# INLINE pFromJSVal #-}

instance ToJSVal AudioContext where
  toJSVal :: AudioContext -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AudioContext -> JSVal) -> AudioContext -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioContext -> JSVal
unAudioContext
  {-# INLINE toJSVal #-}

instance FromJSVal AudioContext where
  fromJSVal :: JSVal -> JSM (Maybe AudioContext)
fromJSVal JSVal
v = (JSVal -> AudioContext) -> Maybe JSVal -> Maybe AudioContext
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AudioContext
AudioContext (Maybe JSVal -> Maybe AudioContext)
-> JSM (Maybe JSVal) -> JSM (Maybe AudioContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AudioContext
fromJSValUnchecked = AudioContext -> JSM AudioContext
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioContext -> JSM AudioContext)
-> (JSVal -> AudioContext) -> JSVal -> JSM AudioContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AudioContext
AudioContext
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AudioContext where
  makeObject :: AudioContext -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AudioContext -> JSVal) -> AudioContext -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioContext -> JSVal
unAudioContext

class (IsEventTarget o, IsGObject o) => IsAudioContext o
toAudioContext :: IsAudioContext o => o -> AudioContext
toAudioContext :: forall o. IsAudioContext o => o -> AudioContext
toAudioContext = JSVal -> AudioContext
AudioContext (JSVal -> AudioContext) -> (o -> JSVal) -> o -> AudioContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsAudioContext AudioContext
instance IsEventTarget AudioContext
instance IsGObject AudioContext where
  typeGType :: AudioContext -> JSM GType
typeGType AudioContext
_ = JSM GType
gTypeAudioContext
  {-# INLINE typeGType #-}

noAudioContext :: Maybe AudioContext
noAudioContext :: Maybe AudioContext
noAudioContext = Maybe AudioContext
forall a. Maybe a
Nothing
{-# INLINE noAudioContext #-}

gTypeAudioContext :: JSM GType
gTypeAudioContext :: JSM GType
gTypeAudioContext = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AudioContext"

-- | Functions for this inteface are in "JSDOM.AudioDestinationNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AudioDestinationNode Mozilla AudioDestinationNode documentation>
newtype AudioDestinationNode = AudioDestinationNode { AudioDestinationNode -> JSVal
unAudioDestinationNode :: JSVal }

instance PToJSVal AudioDestinationNode where
  pToJSVal :: AudioDestinationNode -> JSVal
pToJSVal = AudioDestinationNode -> JSVal
unAudioDestinationNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal AudioDestinationNode where
  pFromJSVal :: JSVal -> AudioDestinationNode
pFromJSVal = JSVal -> AudioDestinationNode
AudioDestinationNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal AudioDestinationNode where
  toJSVal :: AudioDestinationNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AudioDestinationNode -> JSVal)
-> AudioDestinationNode
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioDestinationNode -> JSVal
unAudioDestinationNode
  {-# INLINE toJSVal #-}

instance FromJSVal AudioDestinationNode where
  fromJSVal :: JSVal -> JSM (Maybe AudioDestinationNode)
fromJSVal JSVal
v = (JSVal -> AudioDestinationNode)
-> Maybe JSVal -> Maybe AudioDestinationNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AudioDestinationNode
AudioDestinationNode (Maybe JSVal -> Maybe AudioDestinationNode)
-> JSM (Maybe JSVal) -> JSM (Maybe AudioDestinationNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AudioDestinationNode
fromJSValUnchecked = AudioDestinationNode -> JSM AudioDestinationNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioDestinationNode -> JSM AudioDestinationNode)
-> (JSVal -> AudioDestinationNode)
-> JSVal
-> JSM AudioDestinationNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AudioDestinationNode
AudioDestinationNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AudioDestinationNode where
  makeObject :: AudioDestinationNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AudioDestinationNode -> JSVal)
-> AudioDestinationNode
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioDestinationNode -> JSVal
unAudioDestinationNode

instance IsAudioNode AudioDestinationNode
instance IsEventTarget AudioDestinationNode
instance IsGObject AudioDestinationNode where
  typeGType :: AudioDestinationNode -> JSM GType
typeGType AudioDestinationNode
_ = JSM GType
gTypeAudioDestinationNode
  {-# INLINE typeGType #-}

noAudioDestinationNode :: Maybe AudioDestinationNode
noAudioDestinationNode :: Maybe AudioDestinationNode
noAudioDestinationNode = Maybe AudioDestinationNode
forall a. Maybe a
Nothing
{-# INLINE noAudioDestinationNode #-}

gTypeAudioDestinationNode :: JSM GType
gTypeAudioDestinationNode :: JSM GType
gTypeAudioDestinationNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AudioDestinationNode"

-- | Functions for this inteface are in "JSDOM.AudioListener".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AudioListener Mozilla AudioListener documentation>
newtype AudioListener = AudioListener { AudioListener -> JSVal
unAudioListener :: JSVal }

instance PToJSVal AudioListener where
  pToJSVal :: AudioListener -> JSVal
pToJSVal = AudioListener -> JSVal
unAudioListener
  {-# INLINE pToJSVal #-}

instance PFromJSVal AudioListener where
  pFromJSVal :: JSVal -> AudioListener
pFromJSVal = JSVal -> AudioListener
AudioListener
  {-# INLINE pFromJSVal #-}

instance ToJSVal AudioListener where
  toJSVal :: AudioListener -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AudioListener -> JSVal) -> AudioListener -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioListener -> JSVal
unAudioListener
  {-# INLINE toJSVal #-}

instance FromJSVal AudioListener where
  fromJSVal :: JSVal -> JSM (Maybe AudioListener)
fromJSVal JSVal
v = (JSVal -> AudioListener) -> Maybe JSVal -> Maybe AudioListener
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AudioListener
AudioListener (Maybe JSVal -> Maybe AudioListener)
-> JSM (Maybe JSVal) -> JSM (Maybe AudioListener)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AudioListener
fromJSValUnchecked = AudioListener -> JSM AudioListener
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioListener -> JSM AudioListener)
-> (JSVal -> AudioListener) -> JSVal -> JSM AudioListener
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AudioListener
AudioListener
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AudioListener where
  makeObject :: AudioListener -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AudioListener -> JSVal) -> AudioListener -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioListener -> JSVal
unAudioListener

instance IsGObject AudioListener where
  typeGType :: AudioListener -> JSM GType
typeGType AudioListener
_ = JSM GType
gTypeAudioListener
  {-# INLINE typeGType #-}

noAudioListener :: Maybe AudioListener
noAudioListener :: Maybe AudioListener
noAudioListener = Maybe AudioListener
forall a. Maybe a
Nothing
{-# INLINE noAudioListener #-}

gTypeAudioListener :: JSM GType
gTypeAudioListener :: JSM GType
gTypeAudioListener = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AudioListener"

-- | Functions for this inteface are in "JSDOM.AudioNode".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AudioNode Mozilla AudioNode documentation>
newtype AudioNode = AudioNode { AudioNode -> JSVal
unAudioNode :: JSVal }

instance PToJSVal AudioNode where
  pToJSVal :: AudioNode -> JSVal
pToJSVal = AudioNode -> JSVal
unAudioNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal AudioNode where
  pFromJSVal :: JSVal -> AudioNode
pFromJSVal = JSVal -> AudioNode
AudioNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal AudioNode where
  toJSVal :: AudioNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AudioNode -> JSVal) -> AudioNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioNode -> JSVal
unAudioNode
  {-# INLINE toJSVal #-}

instance FromJSVal AudioNode where
  fromJSVal :: JSVal -> JSM (Maybe AudioNode)
fromJSVal JSVal
v = (JSVal -> AudioNode) -> Maybe JSVal -> Maybe AudioNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AudioNode
AudioNode (Maybe JSVal -> Maybe AudioNode)
-> JSM (Maybe JSVal) -> JSM (Maybe AudioNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AudioNode
fromJSValUnchecked = AudioNode -> JSM AudioNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioNode -> JSM AudioNode)
-> (JSVal -> AudioNode) -> JSVal -> JSM AudioNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AudioNode
AudioNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AudioNode where
  makeObject :: AudioNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AudioNode -> JSVal) -> AudioNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioNode -> JSVal
unAudioNode

class (IsEventTarget o, IsGObject o) => IsAudioNode o
toAudioNode :: IsAudioNode o => o -> AudioNode
toAudioNode :: forall o. IsAudioNode o => o -> AudioNode
toAudioNode = JSVal -> AudioNode
AudioNode (JSVal -> AudioNode) -> (o -> JSVal) -> o -> AudioNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsAudioNode AudioNode
instance IsEventTarget AudioNode
instance IsGObject AudioNode where
  typeGType :: AudioNode -> JSM GType
typeGType AudioNode
_ = JSM GType
gTypeAudioNode
  {-# INLINE typeGType #-}

noAudioNode :: Maybe AudioNode
noAudioNode :: Maybe AudioNode
noAudioNode = Maybe AudioNode
forall a. Maybe a
Nothing
{-# INLINE noAudioNode #-}

gTypeAudioNode :: JSM GType
gTypeAudioNode :: JSM GType
gTypeAudioNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AudioNode"

-- | Functions for this inteface are in "JSDOM.AudioParam".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AudioParam Mozilla AudioParam documentation>
newtype AudioParam = AudioParam { AudioParam -> JSVal
unAudioParam :: JSVal }

instance PToJSVal AudioParam where
  pToJSVal :: AudioParam -> JSVal
pToJSVal = AudioParam -> JSVal
unAudioParam
  {-# INLINE pToJSVal #-}

instance PFromJSVal AudioParam where
  pFromJSVal :: JSVal -> AudioParam
pFromJSVal = JSVal -> AudioParam
AudioParam
  {-# INLINE pFromJSVal #-}

instance ToJSVal AudioParam where
  toJSVal :: AudioParam -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AudioParam -> JSVal) -> AudioParam -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioParam -> JSVal
unAudioParam
  {-# INLINE toJSVal #-}

instance FromJSVal AudioParam where
  fromJSVal :: JSVal -> JSM (Maybe AudioParam)
fromJSVal JSVal
v = (JSVal -> AudioParam) -> Maybe JSVal -> Maybe AudioParam
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AudioParam
AudioParam (Maybe JSVal -> Maybe AudioParam)
-> JSM (Maybe JSVal) -> JSM (Maybe AudioParam)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AudioParam
fromJSValUnchecked = AudioParam -> JSM AudioParam
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioParam -> JSM AudioParam)
-> (JSVal -> AudioParam) -> JSVal -> JSM AudioParam
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AudioParam
AudioParam
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AudioParam where
  makeObject :: AudioParam -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AudioParam -> JSVal) -> AudioParam -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioParam -> JSVal
unAudioParam

instance IsGObject AudioParam where
  typeGType :: AudioParam -> JSM GType
typeGType AudioParam
_ = JSM GType
gTypeAudioParam
  {-# INLINE typeGType #-}

noAudioParam :: Maybe AudioParam
noAudioParam :: Maybe AudioParam
noAudioParam = Maybe AudioParam
forall a. Maybe a
Nothing
{-# INLINE noAudioParam #-}

gTypeAudioParam :: JSM GType
gTypeAudioParam :: JSM GType
gTypeAudioParam = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AudioParam"

-- | Functions for this inteface are in "JSDOM.AudioProcessingEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AudioProcessingEvent Mozilla AudioProcessingEvent documentation>
newtype AudioProcessingEvent = AudioProcessingEvent { AudioProcessingEvent -> JSVal
unAudioProcessingEvent :: JSVal }

instance PToJSVal AudioProcessingEvent where
  pToJSVal :: AudioProcessingEvent -> JSVal
pToJSVal = AudioProcessingEvent -> JSVal
unAudioProcessingEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal AudioProcessingEvent where
  pFromJSVal :: JSVal -> AudioProcessingEvent
pFromJSVal = JSVal -> AudioProcessingEvent
AudioProcessingEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal AudioProcessingEvent where
  toJSVal :: AudioProcessingEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AudioProcessingEvent -> JSVal)
-> AudioProcessingEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioProcessingEvent -> JSVal
unAudioProcessingEvent
  {-# INLINE toJSVal #-}

instance FromJSVal AudioProcessingEvent where
  fromJSVal :: JSVal -> JSM (Maybe AudioProcessingEvent)
fromJSVal JSVal
v = (JSVal -> AudioProcessingEvent)
-> Maybe JSVal -> Maybe AudioProcessingEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AudioProcessingEvent
AudioProcessingEvent (Maybe JSVal -> Maybe AudioProcessingEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe AudioProcessingEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AudioProcessingEvent
fromJSValUnchecked = AudioProcessingEvent -> JSM AudioProcessingEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioProcessingEvent -> JSM AudioProcessingEvent)
-> (JSVal -> AudioProcessingEvent)
-> JSVal
-> JSM AudioProcessingEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AudioProcessingEvent
AudioProcessingEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AudioProcessingEvent where
  makeObject :: AudioProcessingEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AudioProcessingEvent -> JSVal)
-> AudioProcessingEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioProcessingEvent -> JSVal
unAudioProcessingEvent

instance IsEvent AudioProcessingEvent
instance IsGObject AudioProcessingEvent where
  typeGType :: AudioProcessingEvent -> JSM GType
typeGType AudioProcessingEvent
_ = JSM GType
gTypeAudioProcessingEvent
  {-# INLINE typeGType #-}

noAudioProcessingEvent :: Maybe AudioProcessingEvent
noAudioProcessingEvent :: Maybe AudioProcessingEvent
noAudioProcessingEvent = Maybe AudioProcessingEvent
forall a. Maybe a
Nothing
{-# INLINE noAudioProcessingEvent #-}

gTypeAudioProcessingEvent :: JSM GType
gTypeAudioProcessingEvent :: JSM GType
gTypeAudioProcessingEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AudioProcessingEvent"

-- | Functions for this inteface are in "JSDOM.AudioTrack".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AudioTrack Mozilla AudioTrack documentation>
newtype AudioTrack = AudioTrack { AudioTrack -> JSVal
unAudioTrack :: JSVal }

instance PToJSVal AudioTrack where
  pToJSVal :: AudioTrack -> JSVal
pToJSVal = AudioTrack -> JSVal
unAudioTrack
  {-# INLINE pToJSVal #-}

instance PFromJSVal AudioTrack where
  pFromJSVal :: JSVal -> AudioTrack
pFromJSVal = JSVal -> AudioTrack
AudioTrack
  {-# INLINE pFromJSVal #-}

instance ToJSVal AudioTrack where
  toJSVal :: AudioTrack -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AudioTrack -> JSVal) -> AudioTrack -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioTrack -> JSVal
unAudioTrack
  {-# INLINE toJSVal #-}

instance FromJSVal AudioTrack where
  fromJSVal :: JSVal -> JSM (Maybe AudioTrack)
fromJSVal JSVal
v = (JSVal -> AudioTrack) -> Maybe JSVal -> Maybe AudioTrack
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AudioTrack
AudioTrack (Maybe JSVal -> Maybe AudioTrack)
-> JSM (Maybe JSVal) -> JSM (Maybe AudioTrack)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AudioTrack
fromJSValUnchecked = AudioTrack -> JSM AudioTrack
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioTrack -> JSM AudioTrack)
-> (JSVal -> AudioTrack) -> JSVal -> JSM AudioTrack
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AudioTrack
AudioTrack
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AudioTrack where
  makeObject :: AudioTrack -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AudioTrack -> JSVal) -> AudioTrack -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioTrack -> JSVal
unAudioTrack

instance IsGObject AudioTrack where
  typeGType :: AudioTrack -> JSM GType
typeGType AudioTrack
_ = JSM GType
gTypeAudioTrack
  {-# INLINE typeGType #-}

noAudioTrack :: Maybe AudioTrack
noAudioTrack :: Maybe AudioTrack
noAudioTrack = Maybe AudioTrack
forall a. Maybe a
Nothing
{-# INLINE noAudioTrack #-}

gTypeAudioTrack :: JSM GType
gTypeAudioTrack :: JSM GType
gTypeAudioTrack = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AudioTrack"

-- | Functions for this inteface are in "JSDOM.AudioTrackList".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AudioTrackList Mozilla AudioTrackList documentation>
newtype AudioTrackList = AudioTrackList { AudioTrackList -> JSVal
unAudioTrackList :: JSVal }

instance PToJSVal AudioTrackList where
  pToJSVal :: AudioTrackList -> JSVal
pToJSVal = AudioTrackList -> JSVal
unAudioTrackList
  {-# INLINE pToJSVal #-}

instance PFromJSVal AudioTrackList where
  pFromJSVal :: JSVal -> AudioTrackList
pFromJSVal = JSVal -> AudioTrackList
AudioTrackList
  {-# INLINE pFromJSVal #-}

instance ToJSVal AudioTrackList where
  toJSVal :: AudioTrackList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AudioTrackList -> JSVal) -> AudioTrackList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioTrackList -> JSVal
unAudioTrackList
  {-# INLINE toJSVal #-}

instance FromJSVal AudioTrackList where
  fromJSVal :: JSVal -> JSM (Maybe AudioTrackList)
fromJSVal JSVal
v = (JSVal -> AudioTrackList) -> Maybe JSVal -> Maybe AudioTrackList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AudioTrackList
AudioTrackList (Maybe JSVal -> Maybe AudioTrackList)
-> JSM (Maybe JSVal) -> JSM (Maybe AudioTrackList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AudioTrackList
fromJSValUnchecked = AudioTrackList -> JSM AudioTrackList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioTrackList -> JSM AudioTrackList)
-> (JSVal -> AudioTrackList) -> JSVal -> JSM AudioTrackList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AudioTrackList
AudioTrackList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AudioTrackList where
  makeObject :: AudioTrackList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AudioTrackList -> JSVal) -> AudioTrackList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AudioTrackList -> JSVal
unAudioTrackList

instance IsEventTarget AudioTrackList
instance IsGObject AudioTrackList where
  typeGType :: AudioTrackList -> JSM GType
typeGType AudioTrackList
_ = JSM GType
gTypeAudioTrackList
  {-# INLINE typeGType #-}

noAudioTrackList :: Maybe AudioTrackList
noAudioTrackList :: Maybe AudioTrackList
noAudioTrackList = Maybe AudioTrackList
forall a. Maybe a
Nothing
{-# INLINE noAudioTrackList #-}

gTypeAudioTrackList :: JSM GType
gTypeAudioTrackList :: JSM GType
gTypeAudioTrackList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AudioTrackList"

-- | Functions for this inteface are in "JSDOM.AutocompleteErrorEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AutocompleteErrorEvent Mozilla AutocompleteErrorEvent documentation>
newtype AutocompleteErrorEvent = AutocompleteErrorEvent { AutocompleteErrorEvent -> JSVal
unAutocompleteErrorEvent :: JSVal }

instance PToJSVal AutocompleteErrorEvent where
  pToJSVal :: AutocompleteErrorEvent -> JSVal
pToJSVal = AutocompleteErrorEvent -> JSVal
unAutocompleteErrorEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal AutocompleteErrorEvent where
  pFromJSVal :: JSVal -> AutocompleteErrorEvent
pFromJSVal = JSVal -> AutocompleteErrorEvent
AutocompleteErrorEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal AutocompleteErrorEvent where
  toJSVal :: AutocompleteErrorEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AutocompleteErrorEvent -> JSVal)
-> AutocompleteErrorEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AutocompleteErrorEvent -> JSVal
unAutocompleteErrorEvent
  {-# INLINE toJSVal #-}

instance FromJSVal AutocompleteErrorEvent where
  fromJSVal :: JSVal -> JSM (Maybe AutocompleteErrorEvent)
fromJSVal JSVal
v = (JSVal -> AutocompleteErrorEvent)
-> Maybe JSVal -> Maybe AutocompleteErrorEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AutocompleteErrorEvent
AutocompleteErrorEvent (Maybe JSVal -> Maybe AutocompleteErrorEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe AutocompleteErrorEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AutocompleteErrorEvent
fromJSValUnchecked = AutocompleteErrorEvent -> JSM AutocompleteErrorEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AutocompleteErrorEvent -> JSM AutocompleteErrorEvent)
-> (JSVal -> AutocompleteErrorEvent)
-> JSVal
-> JSM AutocompleteErrorEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AutocompleteErrorEvent
AutocompleteErrorEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AutocompleteErrorEvent where
  makeObject :: AutocompleteErrorEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AutocompleteErrorEvent -> JSVal)
-> AutocompleteErrorEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AutocompleteErrorEvent -> JSVal
unAutocompleteErrorEvent

instance IsEvent AutocompleteErrorEvent
instance IsGObject AutocompleteErrorEvent where
  typeGType :: AutocompleteErrorEvent -> JSM GType
typeGType AutocompleteErrorEvent
_ = JSM GType
gTypeAutocompleteErrorEvent
  {-# INLINE typeGType #-}

noAutocompleteErrorEvent :: Maybe AutocompleteErrorEvent
noAutocompleteErrorEvent :: Maybe AutocompleteErrorEvent
noAutocompleteErrorEvent = Maybe AutocompleteErrorEvent
forall a. Maybe a
Nothing
{-# INLINE noAutocompleteErrorEvent #-}

gTypeAutocompleteErrorEvent :: JSM GType
gTypeAutocompleteErrorEvent :: JSM GType
gTypeAutocompleteErrorEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AutocompleteErrorEvent"

-- | Functions for this inteface are in "JSDOM.AutocompleteErrorEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/AutocompleteErrorEventInit Mozilla AutocompleteErrorEventInit documentation>
newtype AutocompleteErrorEventInit = AutocompleteErrorEventInit { AutocompleteErrorEventInit -> JSVal
unAutocompleteErrorEventInit :: JSVal }

instance PToJSVal AutocompleteErrorEventInit where
  pToJSVal :: AutocompleteErrorEventInit -> JSVal
pToJSVal = AutocompleteErrorEventInit -> JSVal
unAutocompleteErrorEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal AutocompleteErrorEventInit where
  pFromJSVal :: JSVal -> AutocompleteErrorEventInit
pFromJSVal = JSVal -> AutocompleteErrorEventInit
AutocompleteErrorEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal AutocompleteErrorEventInit where
  toJSVal :: AutocompleteErrorEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (AutocompleteErrorEventInit -> JSVal)
-> AutocompleteErrorEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AutocompleteErrorEventInit -> JSVal
unAutocompleteErrorEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal AutocompleteErrorEventInit where
  fromJSVal :: JSVal -> JSM (Maybe AutocompleteErrorEventInit)
fromJSVal JSVal
v = (JSVal -> AutocompleteErrorEventInit)
-> Maybe JSVal -> Maybe AutocompleteErrorEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> AutocompleteErrorEventInit
AutocompleteErrorEventInit (Maybe JSVal -> Maybe AutocompleteErrorEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe AutocompleteErrorEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM AutocompleteErrorEventInit
fromJSValUnchecked = AutocompleteErrorEventInit -> JSM AutocompleteErrorEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (AutocompleteErrorEventInit -> JSM AutocompleteErrorEventInit)
-> (JSVal -> AutocompleteErrorEventInit)
-> JSVal
-> JSM AutocompleteErrorEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> AutocompleteErrorEventInit
AutocompleteErrorEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject AutocompleteErrorEventInit where
  makeObject :: AutocompleteErrorEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (AutocompleteErrorEventInit -> JSVal)
-> AutocompleteErrorEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AutocompleteErrorEventInit -> JSVal
unAutocompleteErrorEventInit

instance IsEventInit AutocompleteErrorEventInit
instance IsGObject AutocompleteErrorEventInit where
  typeGType :: AutocompleteErrorEventInit -> JSM GType
typeGType AutocompleteErrorEventInit
_ = JSM GType
gTypeAutocompleteErrorEventInit
  {-# INLINE typeGType #-}

noAutocompleteErrorEventInit :: Maybe AutocompleteErrorEventInit
noAutocompleteErrorEventInit :: Maybe AutocompleteErrorEventInit
noAutocompleteErrorEventInit = Maybe AutocompleteErrorEventInit
forall a. Maybe a
Nothing
{-# INLINE noAutocompleteErrorEventInit #-}

gTypeAutocompleteErrorEventInit :: JSM GType
gTypeAutocompleteErrorEventInit :: JSM GType
gTypeAutocompleteErrorEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"AutocompleteErrorEventInit"

-- | Functions for this inteface are in "JSDOM.BarProp".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/BarProp Mozilla BarProp documentation>
newtype BarProp = BarProp { BarProp -> JSVal
unBarProp :: JSVal }

instance PToJSVal BarProp where
  pToJSVal :: BarProp -> JSVal
pToJSVal = BarProp -> JSVal
unBarProp
  {-# INLINE pToJSVal #-}

instance PFromJSVal BarProp where
  pFromJSVal :: JSVal -> BarProp
pFromJSVal = JSVal -> BarProp
BarProp
  {-# INLINE pFromJSVal #-}

instance ToJSVal BarProp where
  toJSVal :: BarProp -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (BarProp -> JSVal) -> BarProp -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BarProp -> JSVal
unBarProp
  {-# INLINE toJSVal #-}

instance FromJSVal BarProp where
  fromJSVal :: JSVal -> JSM (Maybe BarProp)
fromJSVal JSVal
v = (JSVal -> BarProp) -> Maybe JSVal -> Maybe BarProp
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BarProp
BarProp (Maybe JSVal -> Maybe BarProp)
-> JSM (Maybe JSVal) -> JSM (Maybe BarProp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BarProp
fromJSValUnchecked = BarProp -> JSM BarProp
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BarProp -> JSM BarProp)
-> (JSVal -> BarProp) -> JSVal -> JSM BarProp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BarProp
BarProp
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BarProp where
  makeObject :: BarProp -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BarProp -> JSVal) -> BarProp -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BarProp -> JSVal
unBarProp

instance IsGObject BarProp where
  typeGType :: BarProp -> JSM GType
typeGType BarProp
_ = JSM GType
gTypeBarProp
  {-# INLINE typeGType #-}

noBarProp :: Maybe BarProp
noBarProp :: Maybe BarProp
noBarProp = Maybe BarProp
forall a. Maybe a
Nothing
{-# INLINE noBarProp #-}

gTypeBarProp :: JSM GType
gTypeBarProp :: JSM GType
gTypeBarProp = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"BarProp"

-- | Functions for this inteface are in "JSDOM.BasicCredential".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/BasicCredential Mozilla BasicCredential documentation>
newtype BasicCredential = BasicCredential { BasicCredential -> JSVal
unBasicCredential :: JSVal }

instance PToJSVal BasicCredential where
  pToJSVal :: BasicCredential -> JSVal
pToJSVal = BasicCredential -> JSVal
unBasicCredential
  {-# INLINE pToJSVal #-}

instance PFromJSVal BasicCredential where
  pFromJSVal :: JSVal -> BasicCredential
pFromJSVal = JSVal -> BasicCredential
BasicCredential
  {-# INLINE pFromJSVal #-}

instance ToJSVal BasicCredential where
  toJSVal :: BasicCredential -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (BasicCredential -> JSVal) -> BasicCredential -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BasicCredential -> JSVal
unBasicCredential
  {-# INLINE toJSVal #-}

instance FromJSVal BasicCredential where
  fromJSVal :: JSVal -> JSM (Maybe BasicCredential)
fromJSVal JSVal
v = (JSVal -> BasicCredential) -> Maybe JSVal -> Maybe BasicCredential
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BasicCredential
BasicCredential (Maybe JSVal -> Maybe BasicCredential)
-> JSM (Maybe JSVal) -> JSM (Maybe BasicCredential)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BasicCredential
fromJSValUnchecked = BasicCredential -> JSM BasicCredential
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BasicCredential -> JSM BasicCredential)
-> (JSVal -> BasicCredential) -> JSVal -> JSM BasicCredential
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BasicCredential
BasicCredential
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BasicCredential where
  makeObject :: BasicCredential -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BasicCredential -> JSVal) -> BasicCredential -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BasicCredential -> JSVal
unBasicCredential

class (IsGObject o) => IsBasicCredential o
toBasicCredential :: IsBasicCredential o => o -> BasicCredential
toBasicCredential :: forall o. IsBasicCredential o => o -> BasicCredential
toBasicCredential = JSVal -> BasicCredential
BasicCredential (JSVal -> BasicCredential) -> (o -> JSVal) -> o -> BasicCredential
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsBasicCredential BasicCredential
instance IsGObject BasicCredential where
  typeGType :: BasicCredential -> JSM GType
typeGType BasicCredential
_ = JSM GType
gTypeBasicCredential
  {-# INLINE typeGType #-}

noBasicCredential :: Maybe BasicCredential
noBasicCredential :: Maybe BasicCredential
noBasicCredential = Maybe BasicCredential
forall a. Maybe a
Nothing
{-# INLINE noBasicCredential #-}

gTypeBasicCredential :: JSM GType
gTypeBasicCredential :: JSM GType
gTypeBasicCredential = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"BasicCredential"

-- | Functions for this inteface are in "JSDOM.BeforeLoadEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/BeforeLoadEvent Mozilla BeforeLoadEvent documentation>
newtype BeforeLoadEvent = BeforeLoadEvent { BeforeLoadEvent -> JSVal
unBeforeLoadEvent :: JSVal }

instance PToJSVal BeforeLoadEvent where
  pToJSVal :: BeforeLoadEvent -> JSVal
pToJSVal = BeforeLoadEvent -> JSVal
unBeforeLoadEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal BeforeLoadEvent where
  pFromJSVal :: JSVal -> BeforeLoadEvent
pFromJSVal = JSVal -> BeforeLoadEvent
BeforeLoadEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal BeforeLoadEvent where
  toJSVal :: BeforeLoadEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (BeforeLoadEvent -> JSVal) -> BeforeLoadEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BeforeLoadEvent -> JSVal
unBeforeLoadEvent
  {-# INLINE toJSVal #-}

instance FromJSVal BeforeLoadEvent where
  fromJSVal :: JSVal -> JSM (Maybe BeforeLoadEvent)
fromJSVal JSVal
v = (JSVal -> BeforeLoadEvent) -> Maybe JSVal -> Maybe BeforeLoadEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BeforeLoadEvent
BeforeLoadEvent (Maybe JSVal -> Maybe BeforeLoadEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe BeforeLoadEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BeforeLoadEvent
fromJSValUnchecked = BeforeLoadEvent -> JSM BeforeLoadEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BeforeLoadEvent -> JSM BeforeLoadEvent)
-> (JSVal -> BeforeLoadEvent) -> JSVal -> JSM BeforeLoadEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BeforeLoadEvent
BeforeLoadEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BeforeLoadEvent where
  makeObject :: BeforeLoadEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BeforeLoadEvent -> JSVal) -> BeforeLoadEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BeforeLoadEvent -> JSVal
unBeforeLoadEvent

instance IsEvent BeforeLoadEvent
instance IsGObject BeforeLoadEvent where
  typeGType :: BeforeLoadEvent -> JSM GType
typeGType BeforeLoadEvent
_ = JSM GType
gTypeBeforeLoadEvent
  {-# INLINE typeGType #-}

noBeforeLoadEvent :: Maybe BeforeLoadEvent
noBeforeLoadEvent :: Maybe BeforeLoadEvent
noBeforeLoadEvent = Maybe BeforeLoadEvent
forall a. Maybe a
Nothing
{-# INLINE noBeforeLoadEvent #-}

gTypeBeforeLoadEvent :: JSM GType
gTypeBeforeLoadEvent :: JSM GType
gTypeBeforeLoadEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"BeforeLoadEvent"

-- | Functions for this inteface are in "JSDOM.BeforeLoadEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/BeforeLoadEventInit Mozilla BeforeLoadEventInit documentation>
newtype BeforeLoadEventInit = BeforeLoadEventInit { BeforeLoadEventInit -> JSVal
unBeforeLoadEventInit :: JSVal }

instance PToJSVal BeforeLoadEventInit where
  pToJSVal :: BeforeLoadEventInit -> JSVal
pToJSVal = BeforeLoadEventInit -> JSVal
unBeforeLoadEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal BeforeLoadEventInit where
  pFromJSVal :: JSVal -> BeforeLoadEventInit
pFromJSVal = JSVal -> BeforeLoadEventInit
BeforeLoadEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal BeforeLoadEventInit where
  toJSVal :: BeforeLoadEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (BeforeLoadEventInit -> JSVal)
-> BeforeLoadEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BeforeLoadEventInit -> JSVal
unBeforeLoadEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal BeforeLoadEventInit where
  fromJSVal :: JSVal -> JSM (Maybe BeforeLoadEventInit)
fromJSVal JSVal
v = (JSVal -> BeforeLoadEventInit)
-> Maybe JSVal -> Maybe BeforeLoadEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BeforeLoadEventInit
BeforeLoadEventInit (Maybe JSVal -> Maybe BeforeLoadEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe BeforeLoadEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BeforeLoadEventInit
fromJSValUnchecked = BeforeLoadEventInit -> JSM BeforeLoadEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BeforeLoadEventInit -> JSM BeforeLoadEventInit)
-> (JSVal -> BeforeLoadEventInit)
-> JSVal
-> JSM BeforeLoadEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BeforeLoadEventInit
BeforeLoadEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BeforeLoadEventInit where
  makeObject :: BeforeLoadEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BeforeLoadEventInit -> JSVal)
-> BeforeLoadEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BeforeLoadEventInit -> JSVal
unBeforeLoadEventInit

instance IsEventInit BeforeLoadEventInit
instance IsGObject BeforeLoadEventInit where
  typeGType :: BeforeLoadEventInit -> JSM GType
typeGType BeforeLoadEventInit
_ = JSM GType
gTypeBeforeLoadEventInit
  {-# INLINE typeGType #-}

noBeforeLoadEventInit :: Maybe BeforeLoadEventInit
noBeforeLoadEventInit :: Maybe BeforeLoadEventInit
noBeforeLoadEventInit = Maybe BeforeLoadEventInit
forall a. Maybe a
Nothing
{-# INLINE noBeforeLoadEventInit #-}

gTypeBeforeLoadEventInit :: JSM GType
gTypeBeforeLoadEventInit :: JSM GType
gTypeBeforeLoadEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"BeforeLoadEventInit"

-- | Functions for this inteface are in "JSDOM.BeforeUnloadEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/BeforeUnloadEvent Mozilla BeforeUnloadEvent documentation>
newtype BeforeUnloadEvent = BeforeUnloadEvent { BeforeUnloadEvent -> JSVal
unBeforeUnloadEvent :: JSVal }

instance PToJSVal BeforeUnloadEvent where
  pToJSVal :: BeforeUnloadEvent -> JSVal
pToJSVal = BeforeUnloadEvent -> JSVal
unBeforeUnloadEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal BeforeUnloadEvent where
  pFromJSVal :: JSVal -> BeforeUnloadEvent
pFromJSVal = JSVal -> BeforeUnloadEvent
BeforeUnloadEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal BeforeUnloadEvent where
  toJSVal :: BeforeUnloadEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (BeforeUnloadEvent -> JSVal) -> BeforeUnloadEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BeforeUnloadEvent -> JSVal
unBeforeUnloadEvent
  {-# INLINE toJSVal #-}

instance FromJSVal BeforeUnloadEvent where
  fromJSVal :: JSVal -> JSM (Maybe BeforeUnloadEvent)
fromJSVal JSVal
v = (JSVal -> BeforeUnloadEvent)
-> Maybe JSVal -> Maybe BeforeUnloadEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BeforeUnloadEvent
BeforeUnloadEvent (Maybe JSVal -> Maybe BeforeUnloadEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe BeforeUnloadEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BeforeUnloadEvent
fromJSValUnchecked = BeforeUnloadEvent -> JSM BeforeUnloadEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BeforeUnloadEvent -> JSM BeforeUnloadEvent)
-> (JSVal -> BeforeUnloadEvent) -> JSVal -> JSM BeforeUnloadEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BeforeUnloadEvent
BeforeUnloadEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BeforeUnloadEvent where
  makeObject :: BeforeUnloadEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BeforeUnloadEvent -> JSVal) -> BeforeUnloadEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BeforeUnloadEvent -> JSVal
unBeforeUnloadEvent

instance IsEvent BeforeUnloadEvent
instance IsGObject BeforeUnloadEvent where
  typeGType :: BeforeUnloadEvent -> JSM GType
typeGType BeforeUnloadEvent
_ = JSM GType
gTypeBeforeUnloadEvent
  {-# INLINE typeGType #-}

noBeforeUnloadEvent :: Maybe BeforeUnloadEvent
noBeforeUnloadEvent :: Maybe BeforeUnloadEvent
noBeforeUnloadEvent = Maybe BeforeUnloadEvent
forall a. Maybe a
Nothing
{-# INLINE noBeforeUnloadEvent #-}

gTypeBeforeUnloadEvent :: JSM GType
gTypeBeforeUnloadEvent :: JSM GType
gTypeBeforeUnloadEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"BeforeUnloadEvent"

-- | Functions for this inteface are in "JSDOM.BiquadFilterNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/BiquadFilterNode Mozilla BiquadFilterNode documentation>
newtype BiquadFilterNode = BiquadFilterNode { BiquadFilterNode -> JSVal
unBiquadFilterNode :: JSVal }

instance PToJSVal BiquadFilterNode where
  pToJSVal :: BiquadFilterNode -> JSVal
pToJSVal = BiquadFilterNode -> JSVal
unBiquadFilterNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal BiquadFilterNode where
  pFromJSVal :: JSVal -> BiquadFilterNode
pFromJSVal = JSVal -> BiquadFilterNode
BiquadFilterNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal BiquadFilterNode where
  toJSVal :: BiquadFilterNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (BiquadFilterNode -> JSVal) -> BiquadFilterNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BiquadFilterNode -> JSVal
unBiquadFilterNode
  {-# INLINE toJSVal #-}

instance FromJSVal BiquadFilterNode where
  fromJSVal :: JSVal -> JSM (Maybe BiquadFilterNode)
fromJSVal JSVal
v = (JSVal -> BiquadFilterNode)
-> Maybe JSVal -> Maybe BiquadFilterNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BiquadFilterNode
BiquadFilterNode (Maybe JSVal -> Maybe BiquadFilterNode)
-> JSM (Maybe JSVal) -> JSM (Maybe BiquadFilterNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BiquadFilterNode
fromJSValUnchecked = BiquadFilterNode -> JSM BiquadFilterNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BiquadFilterNode -> JSM BiquadFilterNode)
-> (JSVal -> BiquadFilterNode) -> JSVal -> JSM BiquadFilterNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BiquadFilterNode
BiquadFilterNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BiquadFilterNode where
  makeObject :: BiquadFilterNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BiquadFilterNode -> JSVal) -> BiquadFilterNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BiquadFilterNode -> JSVal
unBiquadFilterNode

instance IsAudioNode BiquadFilterNode
instance IsEventTarget BiquadFilterNode
instance IsGObject BiquadFilterNode where
  typeGType :: BiquadFilterNode -> JSM GType
typeGType BiquadFilterNode
_ = JSM GType
gTypeBiquadFilterNode
  {-# INLINE typeGType #-}

noBiquadFilterNode :: Maybe BiquadFilterNode
noBiquadFilterNode :: Maybe BiquadFilterNode
noBiquadFilterNode = Maybe BiquadFilterNode
forall a. Maybe a
Nothing
{-# INLINE noBiquadFilterNode #-}

gTypeBiquadFilterNode :: JSM GType
gTypeBiquadFilterNode :: JSM GType
gTypeBiquadFilterNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"BiquadFilterNode"

-- | Functions for this inteface are in "JSDOM.Blob".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Blob Mozilla Blob documentation>
newtype Blob = Blob { Blob -> JSVal
unBlob :: JSVal }

instance PToJSVal Blob where
  pToJSVal :: Blob -> JSVal
pToJSVal = Blob -> JSVal
unBlob
  {-# INLINE pToJSVal #-}

instance PFromJSVal Blob where
  pFromJSVal :: JSVal -> Blob
pFromJSVal = JSVal -> Blob
Blob
  {-# INLINE pFromJSVal #-}

instance ToJSVal Blob where
  toJSVal :: Blob -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Blob -> JSVal) -> Blob -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blob -> JSVal
unBlob
  {-# INLINE toJSVal #-}

instance FromJSVal Blob where
  fromJSVal :: JSVal -> JSM (Maybe Blob)
fromJSVal JSVal
v = (JSVal -> Blob) -> Maybe JSVal -> Maybe Blob
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Blob
Blob (Maybe JSVal -> Maybe Blob)
-> JSM (Maybe JSVal) -> JSM (Maybe Blob)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Blob
fromJSValUnchecked = Blob -> JSM Blob
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blob -> JSM Blob) -> (JSVal -> Blob) -> JSVal -> JSM Blob
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Blob
Blob
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Blob where
  makeObject :: Blob -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Blob -> JSVal) -> Blob -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blob -> JSVal
unBlob

class (IsGObject o) => IsBlob o
toBlob :: IsBlob o => o -> Blob
toBlob :: forall o. IsBlob o => o -> Blob
toBlob = JSVal -> Blob
Blob (JSVal -> Blob) -> (o -> JSVal) -> o -> Blob
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsBlob Blob
instance IsGObject Blob where
  typeGType :: Blob -> JSM GType
typeGType Blob
_ = JSM GType
gTypeBlob
  {-# INLINE typeGType #-}

noBlob :: Maybe Blob
noBlob :: Maybe Blob
noBlob = Maybe Blob
forall a. Maybe a
Nothing
{-# INLINE noBlob #-}

gTypeBlob :: JSM GType
gTypeBlob :: JSM GType
gTypeBlob = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Blob"

-- | Functions for this inteface are in "JSDOM.BlobPropertyBag".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/BlobPropertyBag Mozilla BlobPropertyBag documentation>
newtype BlobPropertyBag = BlobPropertyBag { BlobPropertyBag -> JSVal
unBlobPropertyBag :: JSVal }

instance PToJSVal BlobPropertyBag where
  pToJSVal :: BlobPropertyBag -> JSVal
pToJSVal = BlobPropertyBag -> JSVal
unBlobPropertyBag
  {-# INLINE pToJSVal #-}

instance PFromJSVal BlobPropertyBag where
  pFromJSVal :: JSVal -> BlobPropertyBag
pFromJSVal = JSVal -> BlobPropertyBag
BlobPropertyBag
  {-# INLINE pFromJSVal #-}

instance ToJSVal BlobPropertyBag where
  toJSVal :: BlobPropertyBag -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (BlobPropertyBag -> JSVal) -> BlobPropertyBag -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlobPropertyBag -> JSVal
unBlobPropertyBag
  {-# INLINE toJSVal #-}

instance FromJSVal BlobPropertyBag where
  fromJSVal :: JSVal -> JSM (Maybe BlobPropertyBag)
fromJSVal JSVal
v = (JSVal -> BlobPropertyBag) -> Maybe JSVal -> Maybe BlobPropertyBag
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> BlobPropertyBag
BlobPropertyBag (Maybe JSVal -> Maybe BlobPropertyBag)
-> JSM (Maybe JSVal) -> JSM (Maybe BlobPropertyBag)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM BlobPropertyBag
fromJSValUnchecked = BlobPropertyBag -> JSM BlobPropertyBag
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (BlobPropertyBag -> JSM BlobPropertyBag)
-> (JSVal -> BlobPropertyBag) -> JSVal -> JSM BlobPropertyBag
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> BlobPropertyBag
BlobPropertyBag
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject BlobPropertyBag where
  makeObject :: BlobPropertyBag -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (BlobPropertyBag -> JSVal) -> BlobPropertyBag -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlobPropertyBag -> JSVal
unBlobPropertyBag

class (IsGObject o) => IsBlobPropertyBag o
toBlobPropertyBag :: IsBlobPropertyBag o => o -> BlobPropertyBag
toBlobPropertyBag :: forall o. IsBlobPropertyBag o => o -> BlobPropertyBag
toBlobPropertyBag = JSVal -> BlobPropertyBag
BlobPropertyBag (JSVal -> BlobPropertyBag) -> (o -> JSVal) -> o -> BlobPropertyBag
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsBlobPropertyBag BlobPropertyBag
instance IsGObject BlobPropertyBag where
  typeGType :: BlobPropertyBag -> JSM GType
typeGType BlobPropertyBag
_ = JSM GType
gTypeBlobPropertyBag
  {-# INLINE typeGType #-}

noBlobPropertyBag :: Maybe BlobPropertyBag
noBlobPropertyBag :: Maybe BlobPropertyBag
noBlobPropertyBag = Maybe BlobPropertyBag
forall a. Maybe a
Nothing
{-# INLINE noBlobPropertyBag #-}

gTypeBlobPropertyBag :: JSM GType
gTypeBlobPropertyBag :: JSM GType
gTypeBlobPropertyBag = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"BlobPropertyBag"

-- | Functions for this inteface are in "JSDOM.Body".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Body Mozilla Body documentation>
newtype Body = Body { Body -> JSVal
unBody :: JSVal }

instance PToJSVal Body where
  pToJSVal :: Body -> JSVal
pToJSVal = Body -> JSVal
unBody
  {-# INLINE pToJSVal #-}

instance PFromJSVal Body where
  pFromJSVal :: JSVal -> Body
pFromJSVal = JSVal -> Body
Body
  {-# INLINE pFromJSVal #-}

instance ToJSVal Body where
  toJSVal :: Body -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Body -> JSVal) -> Body -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Body -> JSVal
unBody
  {-# INLINE toJSVal #-}

instance FromJSVal Body where
  fromJSVal :: JSVal -> JSM (Maybe Body)
fromJSVal JSVal
v = (JSVal -> Body) -> Maybe JSVal -> Maybe Body
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Body
Body (Maybe JSVal -> Maybe Body)
-> JSM (Maybe JSVal) -> JSM (Maybe Body)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Body
fromJSValUnchecked = Body -> JSM Body
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Body -> JSM Body) -> (JSVal -> Body) -> JSVal -> JSM Body
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Body
Body
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Body where
  makeObject :: Body -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Body -> JSVal) -> Body -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Body -> JSVal
unBody

class (IsGObject o) => IsBody o
toBody :: IsBody o => o -> Body
toBody :: forall o. IsBody o => o -> Body
toBody = JSVal -> Body
Body (JSVal -> Body) -> (o -> JSVal) -> o -> Body
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsBody Body
instance IsGObject Body where
  typeGType :: Body -> JSM GType
typeGType Body
_ = JSM GType
gTypeBody
  {-# INLINE typeGType #-}

noBody :: Maybe Body
noBody :: Maybe Body
noBody = Maybe Body
forall a. Maybe a
Nothing
{-# INLINE noBody #-}

gTypeBody :: JSM GType
gTypeBody :: JSM GType
gTypeBody = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Body"

-- | Functions for this inteface are in "JSDOM.ByteLengthQueuingStrategy".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ByteLengthQueuingStrategy Mozilla ByteLengthQueuingStrategy documentation>
newtype ByteLengthQueuingStrategy = ByteLengthQueuingStrategy { ByteLengthQueuingStrategy -> JSVal
unByteLengthQueuingStrategy :: JSVal }

instance PToJSVal ByteLengthQueuingStrategy where
  pToJSVal :: ByteLengthQueuingStrategy -> JSVal
pToJSVal = ByteLengthQueuingStrategy -> JSVal
unByteLengthQueuingStrategy
  {-# INLINE pToJSVal #-}

instance PFromJSVal ByteLengthQueuingStrategy where
  pFromJSVal :: JSVal -> ByteLengthQueuingStrategy
pFromJSVal = JSVal -> ByteLengthQueuingStrategy
ByteLengthQueuingStrategy
  {-# INLINE pFromJSVal #-}

instance ToJSVal ByteLengthQueuingStrategy where
  toJSVal :: ByteLengthQueuingStrategy -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ByteLengthQueuingStrategy -> JSVal)
-> ByteLengthQueuingStrategy
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteLengthQueuingStrategy -> JSVal
unByteLengthQueuingStrategy
  {-# INLINE toJSVal #-}

instance FromJSVal ByteLengthQueuingStrategy where
  fromJSVal :: JSVal -> JSM (Maybe ByteLengthQueuingStrategy)
fromJSVal JSVal
v = (JSVal -> ByteLengthQueuingStrategy)
-> Maybe JSVal -> Maybe ByteLengthQueuingStrategy
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ByteLengthQueuingStrategy
ByteLengthQueuingStrategy (Maybe JSVal -> Maybe ByteLengthQueuingStrategy)
-> JSM (Maybe JSVal) -> JSM (Maybe ByteLengthQueuingStrategy)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ByteLengthQueuingStrategy
fromJSValUnchecked = ByteLengthQueuingStrategy -> JSM ByteLengthQueuingStrategy
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteLengthQueuingStrategy -> JSM ByteLengthQueuingStrategy)
-> (JSVal -> ByteLengthQueuingStrategy)
-> JSVal
-> JSM ByteLengthQueuingStrategy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ByteLengthQueuingStrategy
ByteLengthQueuingStrategy
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ByteLengthQueuingStrategy where
  makeObject :: ByteLengthQueuingStrategy -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ByteLengthQueuingStrategy -> JSVal)
-> ByteLengthQueuingStrategy
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteLengthQueuingStrategy -> JSVal
unByteLengthQueuingStrategy

instance IsGObject ByteLengthQueuingStrategy where
  typeGType :: ByteLengthQueuingStrategy -> JSM GType
typeGType ByteLengthQueuingStrategy
_ = JSM GType
gTypeByteLengthQueuingStrategy
  {-# INLINE typeGType #-}

noByteLengthQueuingStrategy :: Maybe ByteLengthQueuingStrategy
noByteLengthQueuingStrategy :: Maybe ByteLengthQueuingStrategy
noByteLengthQueuingStrategy = Maybe ByteLengthQueuingStrategy
forall a. Maybe a
Nothing
{-# INLINE noByteLengthQueuingStrategy #-}

gTypeByteLengthQueuingStrategy :: JSM GType
gTypeByteLengthQueuingStrategy :: JSM GType
gTypeByteLengthQueuingStrategy = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ByteLengthQueuingStrategy"

-- | Functions for this inteface are in "JSDOM.CDATASection".
-- Base interface functions are in:
--
--     * "JSDOM.Text"
--     * "JSDOM.CharacterData"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Slotable"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CDATASection Mozilla CDATASection documentation>
newtype CDATASection = CDATASection { CDATASection -> JSVal
unCDATASection :: JSVal }

instance PToJSVal CDATASection where
  pToJSVal :: CDATASection -> JSVal
pToJSVal = CDATASection -> JSVal
unCDATASection
  {-# INLINE pToJSVal #-}

instance PFromJSVal CDATASection where
  pFromJSVal :: JSVal -> CDATASection
pFromJSVal = JSVal -> CDATASection
CDATASection
  {-# INLINE pFromJSVal #-}

instance ToJSVal CDATASection where
  toJSVal :: CDATASection -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CDATASection -> JSVal) -> CDATASection -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CDATASection -> JSVal
unCDATASection
  {-# INLINE toJSVal #-}

instance FromJSVal CDATASection where
  fromJSVal :: JSVal -> JSM (Maybe CDATASection)
fromJSVal JSVal
v = (JSVal -> CDATASection) -> Maybe JSVal -> Maybe CDATASection
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CDATASection
CDATASection (Maybe JSVal -> Maybe CDATASection)
-> JSM (Maybe JSVal) -> JSM (Maybe CDATASection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CDATASection
fromJSValUnchecked = CDATASection -> JSM CDATASection
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CDATASection -> JSM CDATASection)
-> (JSVal -> CDATASection) -> JSVal -> JSM CDATASection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CDATASection
CDATASection
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CDATASection where
  makeObject :: CDATASection -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CDATASection -> JSVal) -> CDATASection -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CDATASection -> JSVal
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 :: CDATASection -> JSM GType
typeGType CDATASection
_ = JSM GType
gTypeCDATASection
  {-# INLINE typeGType #-}

noCDATASection :: Maybe CDATASection
noCDATASection :: Maybe CDATASection
noCDATASection = Maybe CDATASection
forall a. Maybe a
Nothing
{-# INLINE noCDATASection #-}

gTypeCDATASection :: JSM GType
gTypeCDATASection :: JSM GType
gTypeCDATASection = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CDATASection"

-- | Functions for this inteface are in "JSDOM.CSS".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSS Mozilla CSS documentation>
newtype CSS = CSS { CSS -> JSVal
unCSS :: JSVal }

instance PToJSVal CSS where
  pToJSVal :: CSS -> JSVal
pToJSVal = CSS -> JSVal
unCSS
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSS where
  pFromJSVal :: JSVal -> CSS
pFromJSVal = JSVal -> CSS
CSS
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSS where
  toJSVal :: CSS -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (CSS -> JSVal) -> CSS -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSS -> JSVal
unCSS
  {-# INLINE toJSVal #-}

instance FromJSVal CSS where
  fromJSVal :: JSVal -> JSM (Maybe CSS)
fromJSVal JSVal
v = (JSVal -> CSS) -> Maybe JSVal -> Maybe CSS
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSS
CSS (Maybe JSVal -> Maybe CSS) -> JSM (Maybe JSVal) -> JSM (Maybe CSS)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSS
fromJSValUnchecked = CSS -> JSM CSS
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSS -> JSM CSS) -> (JSVal -> CSS) -> JSVal -> JSM CSS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSS
CSS
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSS where
  makeObject :: CSS -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (CSS -> JSVal) -> CSS -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSS -> JSVal
unCSS

instance IsGObject CSS where
  typeGType :: CSS -> JSM GType
typeGType CSS
_ = JSM GType
gTypeCSS
  {-# INLINE typeGType #-}

noCSS :: Maybe CSS
noCSS :: Maybe CSS
noCSS = Maybe CSS
forall a. Maybe a
Nothing
{-# INLINE noCSS #-}

gTypeCSS :: JSM GType
gTypeCSS :: JSM GType
gTypeCSS = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSS"

-- | Functions for this inteface are in "JSDOM.CSSFontFaceLoadEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSFontFaceLoadEvent Mozilla CSSFontFaceLoadEvent documentation>
newtype CSSFontFaceLoadEvent = CSSFontFaceLoadEvent { CSSFontFaceLoadEvent -> JSVal
unCSSFontFaceLoadEvent :: JSVal }

instance PToJSVal CSSFontFaceLoadEvent where
  pToJSVal :: CSSFontFaceLoadEvent -> JSVal
pToJSVal = CSSFontFaceLoadEvent -> JSVal
unCSSFontFaceLoadEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSFontFaceLoadEvent where
  pFromJSVal :: JSVal -> CSSFontFaceLoadEvent
pFromJSVal = JSVal -> CSSFontFaceLoadEvent
CSSFontFaceLoadEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSFontFaceLoadEvent where
  toJSVal :: CSSFontFaceLoadEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSFontFaceLoadEvent -> JSVal)
-> CSSFontFaceLoadEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSFontFaceLoadEvent -> JSVal
unCSSFontFaceLoadEvent
  {-# INLINE toJSVal #-}

instance FromJSVal CSSFontFaceLoadEvent where
  fromJSVal :: JSVal -> JSM (Maybe CSSFontFaceLoadEvent)
fromJSVal JSVal
v = (JSVal -> CSSFontFaceLoadEvent)
-> Maybe JSVal -> Maybe CSSFontFaceLoadEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSFontFaceLoadEvent
CSSFontFaceLoadEvent (Maybe JSVal -> Maybe CSSFontFaceLoadEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSFontFaceLoadEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSFontFaceLoadEvent
fromJSValUnchecked = CSSFontFaceLoadEvent -> JSM CSSFontFaceLoadEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSFontFaceLoadEvent -> JSM CSSFontFaceLoadEvent)
-> (JSVal -> CSSFontFaceLoadEvent)
-> JSVal
-> JSM CSSFontFaceLoadEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSFontFaceLoadEvent
CSSFontFaceLoadEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSFontFaceLoadEvent where
  makeObject :: CSSFontFaceLoadEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSFontFaceLoadEvent -> JSVal)
-> CSSFontFaceLoadEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSFontFaceLoadEvent -> JSVal
unCSSFontFaceLoadEvent

instance IsEvent CSSFontFaceLoadEvent
instance IsGObject CSSFontFaceLoadEvent where
  typeGType :: CSSFontFaceLoadEvent -> JSM GType
typeGType CSSFontFaceLoadEvent
_ = JSM GType
gTypeCSSFontFaceLoadEvent
  {-# INLINE typeGType #-}

noCSSFontFaceLoadEvent :: Maybe CSSFontFaceLoadEvent
noCSSFontFaceLoadEvent :: Maybe CSSFontFaceLoadEvent
noCSSFontFaceLoadEvent = Maybe CSSFontFaceLoadEvent
forall a. Maybe a
Nothing
{-# INLINE noCSSFontFaceLoadEvent #-}

gTypeCSSFontFaceLoadEvent :: JSM GType
gTypeCSSFontFaceLoadEvent :: JSM GType
gTypeCSSFontFaceLoadEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSFontFaceLoadEvent"

-- | Functions for this inteface are in "JSDOM.CSSFontFaceLoadEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSFontFaceLoadEventInit Mozilla CSSFontFaceLoadEventInit documentation>
newtype CSSFontFaceLoadEventInit = CSSFontFaceLoadEventInit { CSSFontFaceLoadEventInit -> JSVal
unCSSFontFaceLoadEventInit :: JSVal }

instance PToJSVal CSSFontFaceLoadEventInit where
  pToJSVal :: CSSFontFaceLoadEventInit -> JSVal
pToJSVal = CSSFontFaceLoadEventInit -> JSVal
unCSSFontFaceLoadEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSFontFaceLoadEventInit where
  pFromJSVal :: JSVal -> CSSFontFaceLoadEventInit
pFromJSVal = JSVal -> CSSFontFaceLoadEventInit
CSSFontFaceLoadEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSFontFaceLoadEventInit where
  toJSVal :: CSSFontFaceLoadEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSFontFaceLoadEventInit -> JSVal)
-> CSSFontFaceLoadEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSFontFaceLoadEventInit -> JSVal
unCSSFontFaceLoadEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal CSSFontFaceLoadEventInit where
  fromJSVal :: JSVal -> JSM (Maybe CSSFontFaceLoadEventInit)
fromJSVal JSVal
v = (JSVal -> CSSFontFaceLoadEventInit)
-> Maybe JSVal -> Maybe CSSFontFaceLoadEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSFontFaceLoadEventInit
CSSFontFaceLoadEventInit (Maybe JSVal -> Maybe CSSFontFaceLoadEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSFontFaceLoadEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSFontFaceLoadEventInit
fromJSValUnchecked = CSSFontFaceLoadEventInit -> JSM CSSFontFaceLoadEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSFontFaceLoadEventInit -> JSM CSSFontFaceLoadEventInit)
-> (JSVal -> CSSFontFaceLoadEventInit)
-> JSVal
-> JSM CSSFontFaceLoadEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSFontFaceLoadEventInit
CSSFontFaceLoadEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSFontFaceLoadEventInit where
  makeObject :: CSSFontFaceLoadEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSFontFaceLoadEventInit -> JSVal)
-> CSSFontFaceLoadEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSFontFaceLoadEventInit -> JSVal
unCSSFontFaceLoadEventInit

instance IsEventInit CSSFontFaceLoadEventInit
instance IsGObject CSSFontFaceLoadEventInit where
  typeGType :: CSSFontFaceLoadEventInit -> JSM GType
typeGType CSSFontFaceLoadEventInit
_ = JSM GType
gTypeCSSFontFaceLoadEventInit
  {-# INLINE typeGType #-}

noCSSFontFaceLoadEventInit :: Maybe CSSFontFaceLoadEventInit
noCSSFontFaceLoadEventInit :: Maybe CSSFontFaceLoadEventInit
noCSSFontFaceLoadEventInit = Maybe CSSFontFaceLoadEventInit
forall a. Maybe a
Nothing
{-# INLINE noCSSFontFaceLoadEventInit #-}

gTypeCSSFontFaceLoadEventInit :: JSM GType
gTypeCSSFontFaceLoadEventInit :: JSM GType
gTypeCSSFontFaceLoadEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSFontFaceLoadEventInit"

-- | Functions for this inteface are in "JSDOM.CSSFontFaceRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSFontFaceRule Mozilla CSSFontFaceRule documentation>
newtype CSSFontFaceRule = CSSFontFaceRule { CSSFontFaceRule -> JSVal
unCSSFontFaceRule :: JSVal }

instance PToJSVal CSSFontFaceRule where
  pToJSVal :: CSSFontFaceRule -> JSVal
pToJSVal = CSSFontFaceRule -> JSVal
unCSSFontFaceRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSFontFaceRule where
  pFromJSVal :: JSVal -> CSSFontFaceRule
pFromJSVal = JSVal -> CSSFontFaceRule
CSSFontFaceRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSFontFaceRule where
  toJSVal :: CSSFontFaceRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSFontFaceRule -> JSVal) -> CSSFontFaceRule -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSFontFaceRule -> JSVal
unCSSFontFaceRule
  {-# INLINE toJSVal #-}

instance FromJSVal CSSFontFaceRule where
  fromJSVal :: JSVal -> JSM (Maybe CSSFontFaceRule)
fromJSVal JSVal
v = (JSVal -> CSSFontFaceRule) -> Maybe JSVal -> Maybe CSSFontFaceRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSFontFaceRule
CSSFontFaceRule (Maybe JSVal -> Maybe CSSFontFaceRule)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSFontFaceRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSFontFaceRule
fromJSValUnchecked = CSSFontFaceRule -> JSM CSSFontFaceRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSFontFaceRule -> JSM CSSFontFaceRule)
-> (JSVal -> CSSFontFaceRule) -> JSVal -> JSM CSSFontFaceRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSFontFaceRule
CSSFontFaceRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSFontFaceRule where
  makeObject :: CSSFontFaceRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSFontFaceRule -> JSVal) -> CSSFontFaceRule -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSFontFaceRule -> JSVal
unCSSFontFaceRule

instance IsCSSRule CSSFontFaceRule
instance IsGObject CSSFontFaceRule where
  typeGType :: CSSFontFaceRule -> JSM GType
typeGType CSSFontFaceRule
_ = JSM GType
gTypeCSSFontFaceRule
  {-# INLINE typeGType #-}

noCSSFontFaceRule :: Maybe CSSFontFaceRule
noCSSFontFaceRule :: Maybe CSSFontFaceRule
noCSSFontFaceRule = Maybe CSSFontFaceRule
forall a. Maybe a
Nothing
{-# INLINE noCSSFontFaceRule #-}

gTypeCSSFontFaceRule :: JSM GType
gTypeCSSFontFaceRule :: JSM GType
gTypeCSSFontFaceRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSFontFaceRule"

-- | Functions for this inteface are in "JSDOM.CSSImportRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSImportRule Mozilla CSSImportRule documentation>
newtype CSSImportRule = CSSImportRule { CSSImportRule -> JSVal
unCSSImportRule :: JSVal }

instance PToJSVal CSSImportRule where
  pToJSVal :: CSSImportRule -> JSVal
pToJSVal = CSSImportRule -> JSVal
unCSSImportRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSImportRule where
  pFromJSVal :: JSVal -> CSSImportRule
pFromJSVal = JSVal -> CSSImportRule
CSSImportRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSImportRule where
  toJSVal :: CSSImportRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSImportRule -> JSVal) -> CSSImportRule -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSImportRule -> JSVal
unCSSImportRule
  {-# INLINE toJSVal #-}

instance FromJSVal CSSImportRule where
  fromJSVal :: JSVal -> JSM (Maybe CSSImportRule)
fromJSVal JSVal
v = (JSVal -> CSSImportRule) -> Maybe JSVal -> Maybe CSSImportRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSImportRule
CSSImportRule (Maybe JSVal -> Maybe CSSImportRule)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSImportRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSImportRule
fromJSValUnchecked = CSSImportRule -> JSM CSSImportRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSImportRule -> JSM CSSImportRule)
-> (JSVal -> CSSImportRule) -> JSVal -> JSM CSSImportRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSImportRule
CSSImportRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSImportRule where
  makeObject :: CSSImportRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSImportRule -> JSVal) -> CSSImportRule -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSImportRule -> JSVal
unCSSImportRule

instance IsCSSRule CSSImportRule
instance IsGObject CSSImportRule where
  typeGType :: CSSImportRule -> JSM GType
typeGType CSSImportRule
_ = JSM GType
gTypeCSSImportRule
  {-# INLINE typeGType #-}

noCSSImportRule :: Maybe CSSImportRule
noCSSImportRule :: Maybe CSSImportRule
noCSSImportRule = Maybe CSSImportRule
forall a. Maybe a
Nothing
{-# INLINE noCSSImportRule #-}

gTypeCSSImportRule :: JSM GType
gTypeCSSImportRule :: JSM GType
gTypeCSSImportRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSImportRule"

-- | Functions for this inteface are in "JSDOM.CSSKeyframeRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSKeyframeRule Mozilla CSSKeyframeRule documentation>
newtype CSSKeyframeRule = CSSKeyframeRule { CSSKeyframeRule -> JSVal
unCSSKeyframeRule :: JSVal }

instance PToJSVal CSSKeyframeRule where
  pToJSVal :: CSSKeyframeRule -> JSVal
pToJSVal = CSSKeyframeRule -> JSVal
unCSSKeyframeRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSKeyframeRule where
  pFromJSVal :: JSVal -> CSSKeyframeRule
pFromJSVal = JSVal -> CSSKeyframeRule
CSSKeyframeRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSKeyframeRule where
  toJSVal :: CSSKeyframeRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSKeyframeRule -> JSVal) -> CSSKeyframeRule -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSKeyframeRule -> JSVal
unCSSKeyframeRule
  {-# INLINE toJSVal #-}

instance FromJSVal CSSKeyframeRule where
  fromJSVal :: JSVal -> JSM (Maybe CSSKeyframeRule)
fromJSVal JSVal
v = (JSVal -> CSSKeyframeRule) -> Maybe JSVal -> Maybe CSSKeyframeRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSKeyframeRule
CSSKeyframeRule (Maybe JSVal -> Maybe CSSKeyframeRule)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSKeyframeRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSKeyframeRule
fromJSValUnchecked = CSSKeyframeRule -> JSM CSSKeyframeRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSKeyframeRule -> JSM CSSKeyframeRule)
-> (JSVal -> CSSKeyframeRule) -> JSVal -> JSM CSSKeyframeRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSKeyframeRule
CSSKeyframeRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSKeyframeRule where
  makeObject :: CSSKeyframeRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSKeyframeRule -> JSVal) -> CSSKeyframeRule -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSKeyframeRule -> JSVal
unCSSKeyframeRule

instance IsCSSRule CSSKeyframeRule
instance IsGObject CSSKeyframeRule where
  typeGType :: CSSKeyframeRule -> JSM GType
typeGType CSSKeyframeRule
_ = JSM GType
gTypeCSSKeyframeRule
  {-# INLINE typeGType #-}

noCSSKeyframeRule :: Maybe CSSKeyframeRule
noCSSKeyframeRule :: Maybe CSSKeyframeRule
noCSSKeyframeRule = Maybe CSSKeyframeRule
forall a. Maybe a
Nothing
{-# INLINE noCSSKeyframeRule #-}

gTypeCSSKeyframeRule :: JSM GType
gTypeCSSKeyframeRule :: JSM GType
gTypeCSSKeyframeRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSKeyframeRule"

-- | Functions for this inteface are in "JSDOM.CSSKeyframesRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSKeyframesRule Mozilla CSSKeyframesRule documentation>
newtype CSSKeyframesRule = CSSKeyframesRule { CSSKeyframesRule -> JSVal
unCSSKeyframesRule :: JSVal }

instance PToJSVal CSSKeyframesRule where
  pToJSVal :: CSSKeyframesRule -> JSVal
pToJSVal = CSSKeyframesRule -> JSVal
unCSSKeyframesRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSKeyframesRule where
  pFromJSVal :: JSVal -> CSSKeyframesRule
pFromJSVal = JSVal -> CSSKeyframesRule
CSSKeyframesRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSKeyframesRule where
  toJSVal :: CSSKeyframesRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSKeyframesRule -> JSVal) -> CSSKeyframesRule -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSKeyframesRule -> JSVal
unCSSKeyframesRule
  {-# INLINE toJSVal #-}

instance FromJSVal CSSKeyframesRule where
  fromJSVal :: JSVal -> JSM (Maybe CSSKeyframesRule)
fromJSVal JSVal
v = (JSVal -> CSSKeyframesRule)
-> Maybe JSVal -> Maybe CSSKeyframesRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSKeyframesRule
CSSKeyframesRule (Maybe JSVal -> Maybe CSSKeyframesRule)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSKeyframesRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSKeyframesRule
fromJSValUnchecked = CSSKeyframesRule -> JSM CSSKeyframesRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSKeyframesRule -> JSM CSSKeyframesRule)
-> (JSVal -> CSSKeyframesRule) -> JSVal -> JSM CSSKeyframesRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSKeyframesRule
CSSKeyframesRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSKeyframesRule where
  makeObject :: CSSKeyframesRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSKeyframesRule -> JSVal) -> CSSKeyframesRule -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSKeyframesRule -> JSVal
unCSSKeyframesRule

instance IsCSSRule CSSKeyframesRule
instance IsGObject CSSKeyframesRule where
  typeGType :: CSSKeyframesRule -> JSM GType
typeGType CSSKeyframesRule
_ = JSM GType
gTypeCSSKeyframesRule
  {-# INLINE typeGType #-}

noCSSKeyframesRule :: Maybe CSSKeyframesRule
noCSSKeyframesRule :: Maybe CSSKeyframesRule
noCSSKeyframesRule = Maybe CSSKeyframesRule
forall a. Maybe a
Nothing
{-# INLINE noCSSKeyframesRule #-}

gTypeCSSKeyframesRule :: JSM GType
gTypeCSSKeyframesRule :: JSM GType
gTypeCSSKeyframesRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSKeyframesRule"

-- | Functions for this inteface are in "JSDOM.CSSMediaRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSMediaRule Mozilla CSSMediaRule documentation>
newtype CSSMediaRule = CSSMediaRule { CSSMediaRule -> JSVal
unCSSMediaRule :: JSVal }

instance PToJSVal CSSMediaRule where
  pToJSVal :: CSSMediaRule -> JSVal
pToJSVal = CSSMediaRule -> JSVal
unCSSMediaRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSMediaRule where
  pFromJSVal :: JSVal -> CSSMediaRule
pFromJSVal = JSVal -> CSSMediaRule
CSSMediaRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSMediaRule where
  toJSVal :: CSSMediaRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSMediaRule -> JSVal) -> CSSMediaRule -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSMediaRule -> JSVal
unCSSMediaRule
  {-# INLINE toJSVal #-}

instance FromJSVal CSSMediaRule where
  fromJSVal :: JSVal -> JSM (Maybe CSSMediaRule)
fromJSVal JSVal
v = (JSVal -> CSSMediaRule) -> Maybe JSVal -> Maybe CSSMediaRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSMediaRule
CSSMediaRule (Maybe JSVal -> Maybe CSSMediaRule)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSMediaRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSMediaRule
fromJSValUnchecked = CSSMediaRule -> JSM CSSMediaRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSMediaRule -> JSM CSSMediaRule)
-> (JSVal -> CSSMediaRule) -> JSVal -> JSM CSSMediaRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSMediaRule
CSSMediaRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSMediaRule where
  makeObject :: CSSMediaRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSMediaRule -> JSVal) -> CSSMediaRule -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSMediaRule -> JSVal
unCSSMediaRule

instance IsCSSRule CSSMediaRule
instance IsGObject CSSMediaRule where
  typeGType :: CSSMediaRule -> JSM GType
typeGType CSSMediaRule
_ = JSM GType
gTypeCSSMediaRule
  {-# INLINE typeGType #-}

noCSSMediaRule :: Maybe CSSMediaRule
noCSSMediaRule :: Maybe CSSMediaRule
noCSSMediaRule = Maybe CSSMediaRule
forall a. Maybe a
Nothing
{-# INLINE noCSSMediaRule #-}

gTypeCSSMediaRule :: JSM GType
gTypeCSSMediaRule :: JSM GType
gTypeCSSMediaRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSMediaRule"

-- | Functions for this inteface are in "JSDOM.CSSNamespaceRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSNamespaceRule Mozilla CSSNamespaceRule documentation>
newtype CSSNamespaceRule = CSSNamespaceRule { CSSNamespaceRule -> JSVal
unCSSNamespaceRule :: JSVal }

instance PToJSVal CSSNamespaceRule where
  pToJSVal :: CSSNamespaceRule -> JSVal
pToJSVal = CSSNamespaceRule -> JSVal
unCSSNamespaceRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSNamespaceRule where
  pFromJSVal :: JSVal -> CSSNamespaceRule
pFromJSVal = JSVal -> CSSNamespaceRule
CSSNamespaceRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSNamespaceRule where
  toJSVal :: CSSNamespaceRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSNamespaceRule -> JSVal) -> CSSNamespaceRule -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSNamespaceRule -> JSVal
unCSSNamespaceRule
  {-# INLINE toJSVal #-}

instance FromJSVal CSSNamespaceRule where
  fromJSVal :: JSVal -> JSM (Maybe CSSNamespaceRule)
fromJSVal JSVal
v = (JSVal -> CSSNamespaceRule)
-> Maybe JSVal -> Maybe CSSNamespaceRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSNamespaceRule
CSSNamespaceRule (Maybe JSVal -> Maybe CSSNamespaceRule)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSNamespaceRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSNamespaceRule
fromJSValUnchecked = CSSNamespaceRule -> JSM CSSNamespaceRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSNamespaceRule -> JSM CSSNamespaceRule)
-> (JSVal -> CSSNamespaceRule) -> JSVal -> JSM CSSNamespaceRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSNamespaceRule
CSSNamespaceRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSNamespaceRule where
  makeObject :: CSSNamespaceRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSNamespaceRule -> JSVal) -> CSSNamespaceRule -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSNamespaceRule -> JSVal
unCSSNamespaceRule

instance IsCSSRule CSSNamespaceRule
instance IsGObject CSSNamespaceRule where
  typeGType :: CSSNamespaceRule -> JSM GType
typeGType CSSNamespaceRule
_ = JSM GType
gTypeCSSNamespaceRule
  {-# INLINE typeGType #-}

noCSSNamespaceRule :: Maybe CSSNamespaceRule
noCSSNamespaceRule :: Maybe CSSNamespaceRule
noCSSNamespaceRule = Maybe CSSNamespaceRule
forall a. Maybe a
Nothing
{-# INLINE noCSSNamespaceRule #-}

gTypeCSSNamespaceRule :: JSM GType
gTypeCSSNamespaceRule :: JSM GType
gTypeCSSNamespaceRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSNamespaceRule"

-- | Functions for this inteface are in "JSDOM.CSSPageRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSPageRule Mozilla CSSPageRule documentation>
newtype CSSPageRule = CSSPageRule { CSSPageRule -> JSVal
unCSSPageRule :: JSVal }

instance PToJSVal CSSPageRule where
  pToJSVal :: CSSPageRule -> JSVal
pToJSVal = CSSPageRule -> JSVal
unCSSPageRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSPageRule where
  pFromJSVal :: JSVal -> CSSPageRule
pFromJSVal = JSVal -> CSSPageRule
CSSPageRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSPageRule where
  toJSVal :: CSSPageRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSPageRule -> JSVal) -> CSSPageRule -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSPageRule -> JSVal
unCSSPageRule
  {-# INLINE toJSVal #-}

instance FromJSVal CSSPageRule where
  fromJSVal :: JSVal -> JSM (Maybe CSSPageRule)
fromJSVal JSVal
v = (JSVal -> CSSPageRule) -> Maybe JSVal -> Maybe CSSPageRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSPageRule
CSSPageRule (Maybe JSVal -> Maybe CSSPageRule)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSPageRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSPageRule
fromJSValUnchecked = CSSPageRule -> JSM CSSPageRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSPageRule -> JSM CSSPageRule)
-> (JSVal -> CSSPageRule) -> JSVal -> JSM CSSPageRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSPageRule
CSSPageRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSPageRule where
  makeObject :: CSSPageRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSPageRule -> JSVal) -> CSSPageRule -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSPageRule -> JSVal
unCSSPageRule

instance IsCSSRule CSSPageRule
instance IsGObject CSSPageRule where
  typeGType :: CSSPageRule -> JSM GType
typeGType CSSPageRule
_ = JSM GType
gTypeCSSPageRule
  {-# INLINE typeGType #-}

noCSSPageRule :: Maybe CSSPageRule
noCSSPageRule :: Maybe CSSPageRule
noCSSPageRule = Maybe CSSPageRule
forall a. Maybe a
Nothing
{-# INLINE noCSSPageRule #-}

gTypeCSSPageRule :: JSM GType
gTypeCSSPageRule :: JSM GType
gTypeCSSPageRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSPageRule"

-- | Functions for this inteface are in "JSDOM.CSSPrimitiveValue".
-- Base interface functions are in:
--
--     * "JSDOM.CSSValue"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSPrimitiveValue Mozilla CSSPrimitiveValue documentation>
newtype CSSPrimitiveValue = CSSPrimitiveValue { CSSPrimitiveValue -> JSVal
unCSSPrimitiveValue :: JSVal }

instance PToJSVal CSSPrimitiveValue where
  pToJSVal :: CSSPrimitiveValue -> JSVal
pToJSVal = CSSPrimitiveValue -> JSVal
unCSSPrimitiveValue
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSPrimitiveValue where
  pFromJSVal :: JSVal -> CSSPrimitiveValue
pFromJSVal = JSVal -> CSSPrimitiveValue
CSSPrimitiveValue
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSPrimitiveValue where
  toJSVal :: CSSPrimitiveValue -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSPrimitiveValue -> JSVal) -> CSSPrimitiveValue -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSPrimitiveValue -> JSVal
unCSSPrimitiveValue
  {-# INLINE toJSVal #-}

instance FromJSVal CSSPrimitiveValue where
  fromJSVal :: JSVal -> JSM (Maybe CSSPrimitiveValue)
fromJSVal JSVal
v = (JSVal -> CSSPrimitiveValue)
-> Maybe JSVal -> Maybe CSSPrimitiveValue
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSPrimitiveValue
CSSPrimitiveValue (Maybe JSVal -> Maybe CSSPrimitiveValue)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSPrimitiveValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSPrimitiveValue
fromJSValUnchecked = CSSPrimitiveValue -> JSM CSSPrimitiveValue
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSPrimitiveValue -> JSM CSSPrimitiveValue)
-> (JSVal -> CSSPrimitiveValue) -> JSVal -> JSM CSSPrimitiveValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSPrimitiveValue
CSSPrimitiveValue
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSPrimitiveValue where
  makeObject :: CSSPrimitiveValue -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSPrimitiveValue -> JSVal) -> CSSPrimitiveValue -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSPrimitiveValue -> JSVal
unCSSPrimitiveValue

instance IsCSSValue CSSPrimitiveValue
instance IsGObject CSSPrimitiveValue where
  typeGType :: CSSPrimitiveValue -> JSM GType
typeGType CSSPrimitiveValue
_ = JSM GType
gTypeCSSPrimitiveValue
  {-# INLINE typeGType #-}

noCSSPrimitiveValue :: Maybe CSSPrimitiveValue
noCSSPrimitiveValue :: Maybe CSSPrimitiveValue
noCSSPrimitiveValue = Maybe CSSPrimitiveValue
forall a. Maybe a
Nothing
{-# INLINE noCSSPrimitiveValue #-}

gTypeCSSPrimitiveValue :: JSM GType
gTypeCSSPrimitiveValue :: JSM GType
gTypeCSSPrimitiveValue = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSPrimitiveValue"

-- | Functions for this inteface are in "JSDOM.CSSRule".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSRule Mozilla CSSRule documentation>
newtype CSSRule = CSSRule { CSSRule -> JSVal
unCSSRule :: JSVal }

instance PToJSVal CSSRule where
  pToJSVal :: CSSRule -> JSVal
pToJSVal = CSSRule -> JSVal
unCSSRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSRule where
  pFromJSVal :: JSVal -> CSSRule
pFromJSVal = JSVal -> CSSRule
CSSRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSRule where
  toJSVal :: CSSRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (CSSRule -> JSVal) -> CSSRule -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSRule -> JSVal
unCSSRule
  {-# INLINE toJSVal #-}

instance FromJSVal CSSRule where
  fromJSVal :: JSVal -> JSM (Maybe CSSRule)
fromJSVal JSVal
v = (JSVal -> CSSRule) -> Maybe JSVal -> Maybe CSSRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSRule
CSSRule (Maybe JSVal -> Maybe CSSRule)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSRule
fromJSValUnchecked = CSSRule -> JSM CSSRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSRule -> JSM CSSRule)
-> (JSVal -> CSSRule) -> JSVal -> JSM CSSRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSRule
CSSRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSRule where
  makeObject :: CSSRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSRule -> JSVal) -> CSSRule -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSRule -> JSVal
unCSSRule

class (IsGObject o) => IsCSSRule o
toCSSRule :: IsCSSRule o => o -> CSSRule
toCSSRule :: forall o. IsCSSRule o => o -> CSSRule
toCSSRule = JSVal -> CSSRule
CSSRule (JSVal -> CSSRule) -> (o -> JSVal) -> o -> CSSRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsCSSRule CSSRule
instance IsGObject CSSRule where
  typeGType :: CSSRule -> JSM GType
typeGType CSSRule
_ = JSM GType
gTypeCSSRule
  {-# INLINE typeGType #-}

noCSSRule :: Maybe CSSRule
noCSSRule :: Maybe CSSRule
noCSSRule = Maybe CSSRule
forall a. Maybe a
Nothing
{-# INLINE noCSSRule #-}

gTypeCSSRule :: JSM GType
gTypeCSSRule :: JSM GType
gTypeCSSRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSRule"

-- | Functions for this inteface are in "JSDOM.CSSRuleList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSRuleList Mozilla CSSRuleList documentation>
newtype CSSRuleList = CSSRuleList { CSSRuleList -> JSVal
unCSSRuleList :: JSVal }

instance PToJSVal CSSRuleList where
  pToJSVal :: CSSRuleList -> JSVal
pToJSVal = CSSRuleList -> JSVal
unCSSRuleList
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSRuleList where
  pFromJSVal :: JSVal -> CSSRuleList
pFromJSVal = JSVal -> CSSRuleList
CSSRuleList
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSRuleList where
  toJSVal :: CSSRuleList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSRuleList -> JSVal) -> CSSRuleList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSRuleList -> JSVal
unCSSRuleList
  {-# INLINE toJSVal #-}

instance FromJSVal CSSRuleList where
  fromJSVal :: JSVal -> JSM (Maybe CSSRuleList)
fromJSVal JSVal
v = (JSVal -> CSSRuleList) -> Maybe JSVal -> Maybe CSSRuleList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSRuleList
CSSRuleList (Maybe JSVal -> Maybe CSSRuleList)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSRuleList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSRuleList
fromJSValUnchecked = CSSRuleList -> JSM CSSRuleList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSRuleList -> JSM CSSRuleList)
-> (JSVal -> CSSRuleList) -> JSVal -> JSM CSSRuleList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSRuleList
CSSRuleList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSRuleList where
  makeObject :: CSSRuleList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSRuleList -> JSVal) -> CSSRuleList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSRuleList -> JSVal
unCSSRuleList

instance IsGObject CSSRuleList where
  typeGType :: CSSRuleList -> JSM GType
typeGType CSSRuleList
_ = JSM GType
gTypeCSSRuleList
  {-# INLINE typeGType #-}

noCSSRuleList :: Maybe CSSRuleList
noCSSRuleList :: Maybe CSSRuleList
noCSSRuleList = Maybe CSSRuleList
forall a. Maybe a
Nothing
{-# INLINE noCSSRuleList #-}

gTypeCSSRuleList :: JSM GType
gTypeCSSRuleList :: JSM GType
gTypeCSSRuleList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSRuleList"

-- | Functions for this inteface are in "JSDOM.CSSStyleDeclaration".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSStyleDeclaration Mozilla CSSStyleDeclaration documentation>
newtype CSSStyleDeclaration = CSSStyleDeclaration { CSSStyleDeclaration -> JSVal
unCSSStyleDeclaration :: JSVal }

instance PToJSVal CSSStyleDeclaration where
  pToJSVal :: CSSStyleDeclaration -> JSVal
pToJSVal = CSSStyleDeclaration -> JSVal
unCSSStyleDeclaration
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSStyleDeclaration where
  pFromJSVal :: JSVal -> CSSStyleDeclaration
pFromJSVal = JSVal -> CSSStyleDeclaration
CSSStyleDeclaration
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSStyleDeclaration where
  toJSVal :: CSSStyleDeclaration -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSStyleDeclaration -> JSVal)
-> CSSStyleDeclaration
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSStyleDeclaration -> JSVal
unCSSStyleDeclaration
  {-# INLINE toJSVal #-}

instance FromJSVal CSSStyleDeclaration where
  fromJSVal :: JSVal -> JSM (Maybe CSSStyleDeclaration)
fromJSVal JSVal
v = (JSVal -> CSSStyleDeclaration)
-> Maybe JSVal -> Maybe CSSStyleDeclaration
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSStyleDeclaration
CSSStyleDeclaration (Maybe JSVal -> Maybe CSSStyleDeclaration)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSStyleDeclaration)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSStyleDeclaration
fromJSValUnchecked = CSSStyleDeclaration -> JSM CSSStyleDeclaration
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSStyleDeclaration -> JSM CSSStyleDeclaration)
-> (JSVal -> CSSStyleDeclaration)
-> JSVal
-> JSM CSSStyleDeclaration
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSStyleDeclaration
CSSStyleDeclaration
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSStyleDeclaration where
  makeObject :: CSSStyleDeclaration -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSStyleDeclaration -> JSVal)
-> CSSStyleDeclaration
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSStyleDeclaration -> JSVal
unCSSStyleDeclaration

instance IsGObject CSSStyleDeclaration where
  typeGType :: CSSStyleDeclaration -> JSM GType
typeGType CSSStyleDeclaration
_ = JSM GType
gTypeCSSStyleDeclaration
  {-# INLINE typeGType #-}

noCSSStyleDeclaration :: Maybe CSSStyleDeclaration
noCSSStyleDeclaration :: Maybe CSSStyleDeclaration
noCSSStyleDeclaration = Maybe CSSStyleDeclaration
forall a. Maybe a
Nothing
{-# INLINE noCSSStyleDeclaration #-}

gTypeCSSStyleDeclaration :: JSM GType
gTypeCSSStyleDeclaration :: JSM GType
gTypeCSSStyleDeclaration = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSStyleDeclaration"

-- | Functions for this inteface are in "JSDOM.CSSStyleRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSStyleRule Mozilla CSSStyleRule documentation>
newtype CSSStyleRule = CSSStyleRule { CSSStyleRule -> JSVal
unCSSStyleRule :: JSVal }

instance PToJSVal CSSStyleRule where
  pToJSVal :: CSSStyleRule -> JSVal
pToJSVal = CSSStyleRule -> JSVal
unCSSStyleRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSStyleRule where
  pFromJSVal :: JSVal -> CSSStyleRule
pFromJSVal = JSVal -> CSSStyleRule
CSSStyleRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSStyleRule where
  toJSVal :: CSSStyleRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSStyleRule -> JSVal) -> CSSStyleRule -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSStyleRule -> JSVal
unCSSStyleRule
  {-# INLINE toJSVal #-}

instance FromJSVal CSSStyleRule where
  fromJSVal :: JSVal -> JSM (Maybe CSSStyleRule)
fromJSVal JSVal
v = (JSVal -> CSSStyleRule) -> Maybe JSVal -> Maybe CSSStyleRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSStyleRule
CSSStyleRule (Maybe JSVal -> Maybe CSSStyleRule)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSStyleRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSStyleRule
fromJSValUnchecked = CSSStyleRule -> JSM CSSStyleRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSStyleRule -> JSM CSSStyleRule)
-> (JSVal -> CSSStyleRule) -> JSVal -> JSM CSSStyleRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSStyleRule
CSSStyleRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSStyleRule where
  makeObject :: CSSStyleRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSStyleRule -> JSVal) -> CSSStyleRule -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSStyleRule -> JSVal
unCSSStyleRule

instance IsCSSRule CSSStyleRule
instance IsGObject CSSStyleRule where
  typeGType :: CSSStyleRule -> JSM GType
typeGType CSSStyleRule
_ = JSM GType
gTypeCSSStyleRule
  {-# INLINE typeGType #-}

noCSSStyleRule :: Maybe CSSStyleRule
noCSSStyleRule :: Maybe CSSStyleRule
noCSSStyleRule = Maybe CSSStyleRule
forall a. Maybe a
Nothing
{-# INLINE noCSSStyleRule #-}

gTypeCSSStyleRule :: JSM GType
gTypeCSSStyleRule :: JSM GType
gTypeCSSStyleRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSStyleRule"

-- | Functions for this inteface are in "JSDOM.CSSStyleSheet".
-- Base interface functions are in:
--
--     * "JSDOM.StyleSheet"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSStyleSheet Mozilla CSSStyleSheet documentation>
newtype CSSStyleSheet = CSSStyleSheet { CSSStyleSheet -> JSVal
unCSSStyleSheet :: JSVal }

instance PToJSVal CSSStyleSheet where
  pToJSVal :: CSSStyleSheet -> JSVal
pToJSVal = CSSStyleSheet -> JSVal
unCSSStyleSheet
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSStyleSheet where
  pFromJSVal :: JSVal -> CSSStyleSheet
pFromJSVal = JSVal -> CSSStyleSheet
CSSStyleSheet
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSStyleSheet where
  toJSVal :: CSSStyleSheet -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSStyleSheet -> JSVal) -> CSSStyleSheet -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSStyleSheet -> JSVal
unCSSStyleSheet
  {-# INLINE toJSVal #-}

instance FromJSVal CSSStyleSheet where
  fromJSVal :: JSVal -> JSM (Maybe CSSStyleSheet)
fromJSVal JSVal
v = (JSVal -> CSSStyleSheet) -> Maybe JSVal -> Maybe CSSStyleSheet
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSStyleSheet
CSSStyleSheet (Maybe JSVal -> Maybe CSSStyleSheet)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSStyleSheet)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSStyleSheet
fromJSValUnchecked = CSSStyleSheet -> JSM CSSStyleSheet
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSStyleSheet -> JSM CSSStyleSheet)
-> (JSVal -> CSSStyleSheet) -> JSVal -> JSM CSSStyleSheet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSStyleSheet
CSSStyleSheet
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSStyleSheet where
  makeObject :: CSSStyleSheet -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSStyleSheet -> JSVal) -> CSSStyleSheet -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSStyleSheet -> JSVal
unCSSStyleSheet

instance IsStyleSheet CSSStyleSheet
instance IsGObject CSSStyleSheet where
  typeGType :: CSSStyleSheet -> JSM GType
typeGType CSSStyleSheet
_ = JSM GType
gTypeCSSStyleSheet
  {-# INLINE typeGType #-}

noCSSStyleSheet :: Maybe CSSStyleSheet
noCSSStyleSheet :: Maybe CSSStyleSheet
noCSSStyleSheet = Maybe CSSStyleSheet
forall a. Maybe a
Nothing
{-# INLINE noCSSStyleSheet #-}

gTypeCSSStyleSheet :: JSM GType
gTypeCSSStyleSheet :: JSM GType
gTypeCSSStyleSheet = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSStyleSheet"

-- | Functions for this inteface are in "JSDOM.CSSSupportsRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSSupportsRule Mozilla CSSSupportsRule documentation>
newtype CSSSupportsRule = CSSSupportsRule { CSSSupportsRule -> JSVal
unCSSSupportsRule :: JSVal }

instance PToJSVal CSSSupportsRule where
  pToJSVal :: CSSSupportsRule -> JSVal
pToJSVal = CSSSupportsRule -> JSVal
unCSSSupportsRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSSupportsRule where
  pFromJSVal :: JSVal -> CSSSupportsRule
pFromJSVal = JSVal -> CSSSupportsRule
CSSSupportsRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSSupportsRule where
  toJSVal :: CSSSupportsRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSSupportsRule -> JSVal) -> CSSSupportsRule -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSSupportsRule -> JSVal
unCSSSupportsRule
  {-# INLINE toJSVal #-}

instance FromJSVal CSSSupportsRule where
  fromJSVal :: JSVal -> JSM (Maybe CSSSupportsRule)
fromJSVal JSVal
v = (JSVal -> CSSSupportsRule) -> Maybe JSVal -> Maybe CSSSupportsRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSSupportsRule
CSSSupportsRule (Maybe JSVal -> Maybe CSSSupportsRule)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSSupportsRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSSupportsRule
fromJSValUnchecked = CSSSupportsRule -> JSM CSSSupportsRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSSupportsRule -> JSM CSSSupportsRule)
-> (JSVal -> CSSSupportsRule) -> JSVal -> JSM CSSSupportsRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSSupportsRule
CSSSupportsRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSSupportsRule where
  makeObject :: CSSSupportsRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSSupportsRule -> JSVal) -> CSSSupportsRule -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSSupportsRule -> JSVal
unCSSSupportsRule

instance IsCSSRule CSSSupportsRule
instance IsGObject CSSSupportsRule where
  typeGType :: CSSSupportsRule -> JSM GType
typeGType CSSSupportsRule
_ = JSM GType
gTypeCSSSupportsRule
  {-# INLINE typeGType #-}

noCSSSupportsRule :: Maybe CSSSupportsRule
noCSSSupportsRule :: Maybe CSSSupportsRule
noCSSSupportsRule = Maybe CSSSupportsRule
forall a. Maybe a
Nothing
{-# INLINE noCSSSupportsRule #-}

gTypeCSSSupportsRule :: JSM GType
gTypeCSSSupportsRule :: JSM GType
gTypeCSSSupportsRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSSupportsRule"

-- | Functions for this inteface are in "JSDOM.CSSUnknownRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSUnknownRule Mozilla CSSUnknownRule documentation>
newtype CSSUnknownRule = CSSUnknownRule { CSSUnknownRule -> JSVal
unCSSUnknownRule :: JSVal }

instance PToJSVal CSSUnknownRule where
  pToJSVal :: CSSUnknownRule -> JSVal
pToJSVal = CSSUnknownRule -> JSVal
unCSSUnknownRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSUnknownRule where
  pFromJSVal :: JSVal -> CSSUnknownRule
pFromJSVal = JSVal -> CSSUnknownRule
CSSUnknownRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSUnknownRule where
  toJSVal :: CSSUnknownRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSUnknownRule -> JSVal) -> CSSUnknownRule -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSUnknownRule -> JSVal
unCSSUnknownRule
  {-# INLINE toJSVal #-}

instance FromJSVal CSSUnknownRule where
  fromJSVal :: JSVal -> JSM (Maybe CSSUnknownRule)
fromJSVal JSVal
v = (JSVal -> CSSUnknownRule) -> Maybe JSVal -> Maybe CSSUnknownRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSUnknownRule
CSSUnknownRule (Maybe JSVal -> Maybe CSSUnknownRule)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSUnknownRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSUnknownRule
fromJSValUnchecked = CSSUnknownRule -> JSM CSSUnknownRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSUnknownRule -> JSM CSSUnknownRule)
-> (JSVal -> CSSUnknownRule) -> JSVal -> JSM CSSUnknownRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSUnknownRule
CSSUnknownRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSUnknownRule where
  makeObject :: CSSUnknownRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSUnknownRule -> JSVal) -> CSSUnknownRule -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSUnknownRule -> JSVal
unCSSUnknownRule

instance IsCSSRule CSSUnknownRule
instance IsGObject CSSUnknownRule where
  typeGType :: CSSUnknownRule -> JSM GType
typeGType CSSUnknownRule
_ = JSM GType
gTypeCSSUnknownRule
  {-# INLINE typeGType #-}

noCSSUnknownRule :: Maybe CSSUnknownRule
noCSSUnknownRule :: Maybe CSSUnknownRule
noCSSUnknownRule = Maybe CSSUnknownRule
forall a. Maybe a
Nothing
{-# INLINE noCSSUnknownRule #-}

gTypeCSSUnknownRule :: JSM GType
gTypeCSSUnknownRule :: JSM GType
gTypeCSSUnknownRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSUnknownRule"

-- | Functions for this inteface are in "JSDOM.CSSValue".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSValue Mozilla CSSValue documentation>
newtype CSSValue = CSSValue { CSSValue -> JSVal
unCSSValue :: JSVal }

instance PToJSVal CSSValue where
  pToJSVal :: CSSValue -> JSVal
pToJSVal = CSSValue -> JSVal
unCSSValue
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSValue where
  pFromJSVal :: JSVal -> CSSValue
pFromJSVal = JSVal -> CSSValue
CSSValue
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSValue where
  toJSVal :: CSSValue -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSValue -> JSVal) -> CSSValue -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSValue -> JSVal
unCSSValue
  {-# INLINE toJSVal #-}

instance FromJSVal CSSValue where
  fromJSVal :: JSVal -> JSM (Maybe CSSValue)
fromJSVal JSVal
v = (JSVal -> CSSValue) -> Maybe JSVal -> Maybe CSSValue
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSValue
CSSValue (Maybe JSVal -> Maybe CSSValue)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSValue
fromJSValUnchecked = CSSValue -> JSM CSSValue
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSValue -> JSM CSSValue)
-> (JSVal -> CSSValue) -> JSVal -> JSM CSSValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSValue
CSSValue
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSValue where
  makeObject :: CSSValue -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSValue -> JSVal) -> CSSValue -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSValue -> JSVal
unCSSValue

class (IsGObject o) => IsCSSValue o
toCSSValue :: IsCSSValue o => o -> CSSValue
toCSSValue :: forall o. IsCSSValue o => o -> CSSValue
toCSSValue = JSVal -> CSSValue
CSSValue (JSVal -> CSSValue) -> (o -> JSVal) -> o -> CSSValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsCSSValue CSSValue
instance IsGObject CSSValue where
  typeGType :: CSSValue -> JSM GType
typeGType CSSValue
_ = JSM GType
gTypeCSSValue
  {-# INLINE typeGType #-}

noCSSValue :: Maybe CSSValue
noCSSValue :: Maybe CSSValue
noCSSValue = Maybe CSSValue
forall a. Maybe a
Nothing
{-# INLINE noCSSValue #-}

gTypeCSSValue :: JSM GType
gTypeCSSValue :: JSM GType
gTypeCSSValue = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSValue"

-- | Functions for this inteface are in "JSDOM.CSSValueList".
-- Base interface functions are in:
--
--     * "JSDOM.CSSValue"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CSSValueList Mozilla CSSValueList documentation>
newtype CSSValueList = CSSValueList { CSSValueList -> JSVal
unCSSValueList :: JSVal }

instance PToJSVal CSSValueList where
  pToJSVal :: CSSValueList -> JSVal
pToJSVal = CSSValueList -> JSVal
unCSSValueList
  {-# INLINE pToJSVal #-}

instance PFromJSVal CSSValueList where
  pFromJSVal :: JSVal -> CSSValueList
pFromJSVal = JSVal -> CSSValueList
CSSValueList
  {-# INLINE pFromJSVal #-}

instance ToJSVal CSSValueList where
  toJSVal :: CSSValueList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CSSValueList -> JSVal) -> CSSValueList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSValueList -> JSVal
unCSSValueList
  {-# INLINE toJSVal #-}

instance FromJSVal CSSValueList where
  fromJSVal :: JSVal -> JSM (Maybe CSSValueList)
fromJSVal JSVal
v = (JSVal -> CSSValueList) -> Maybe JSVal -> Maybe CSSValueList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CSSValueList
CSSValueList (Maybe JSVal -> Maybe CSSValueList)
-> JSM (Maybe JSVal) -> JSM (Maybe CSSValueList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CSSValueList
fromJSValUnchecked = CSSValueList -> JSM CSSValueList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSSValueList -> JSM CSSValueList)
-> (JSVal -> CSSValueList) -> JSVal -> JSM CSSValueList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CSSValueList
CSSValueList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CSSValueList where
  makeObject :: CSSValueList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CSSValueList -> JSVal) -> CSSValueList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSSValueList -> JSVal
unCSSValueList

instance IsCSSValue CSSValueList
instance IsGObject CSSValueList where
  typeGType :: CSSValueList -> JSM GType
typeGType CSSValueList
_ = JSM GType
gTypeCSSValueList
  {-# INLINE typeGType #-}

noCSSValueList :: Maybe CSSValueList
noCSSValueList :: Maybe CSSValueList
noCSSValueList = Maybe CSSValueList
forall a. Maybe a
Nothing
{-# INLINE noCSSValueList #-}

gTypeCSSValueList :: JSM GType
gTypeCSSValueList :: JSM GType
gTypeCSSValueList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CSSValueList"

-- | Functions for this inteface are in "JSDOM.CanvasCaptureMediaStreamTrack".
-- Base interface functions are in:
--
--     * "JSDOM.MediaStreamTrack"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CanvasCaptureMediaStreamTrack Mozilla CanvasCaptureMediaStreamTrack documentation>
newtype CanvasCaptureMediaStreamTrack = CanvasCaptureMediaStreamTrack { CanvasCaptureMediaStreamTrack -> JSVal
unCanvasCaptureMediaStreamTrack :: JSVal }

instance PToJSVal CanvasCaptureMediaStreamTrack where
  pToJSVal :: CanvasCaptureMediaStreamTrack -> JSVal
pToJSVal = CanvasCaptureMediaStreamTrack -> JSVal
unCanvasCaptureMediaStreamTrack
  {-# INLINE pToJSVal #-}

instance PFromJSVal CanvasCaptureMediaStreamTrack where
  pFromJSVal :: JSVal -> CanvasCaptureMediaStreamTrack
pFromJSVal = JSVal -> CanvasCaptureMediaStreamTrack
CanvasCaptureMediaStreamTrack
  {-# INLINE pFromJSVal #-}

instance ToJSVal CanvasCaptureMediaStreamTrack where
  toJSVal :: CanvasCaptureMediaStreamTrack -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CanvasCaptureMediaStreamTrack -> JSVal)
-> CanvasCaptureMediaStreamTrack
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasCaptureMediaStreamTrack -> JSVal
unCanvasCaptureMediaStreamTrack
  {-# INLINE toJSVal #-}

instance FromJSVal CanvasCaptureMediaStreamTrack where
  fromJSVal :: JSVal -> JSM (Maybe CanvasCaptureMediaStreamTrack)
fromJSVal JSVal
v = (JSVal -> CanvasCaptureMediaStreamTrack)
-> Maybe JSVal -> Maybe CanvasCaptureMediaStreamTrack
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CanvasCaptureMediaStreamTrack
CanvasCaptureMediaStreamTrack (Maybe JSVal -> Maybe CanvasCaptureMediaStreamTrack)
-> JSM (Maybe JSVal) -> JSM (Maybe CanvasCaptureMediaStreamTrack)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CanvasCaptureMediaStreamTrack
fromJSValUnchecked = CanvasCaptureMediaStreamTrack -> JSM CanvasCaptureMediaStreamTrack
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CanvasCaptureMediaStreamTrack
 -> JSM CanvasCaptureMediaStreamTrack)
-> (JSVal -> CanvasCaptureMediaStreamTrack)
-> JSVal
-> JSM CanvasCaptureMediaStreamTrack
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CanvasCaptureMediaStreamTrack
CanvasCaptureMediaStreamTrack
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CanvasCaptureMediaStreamTrack where
  makeObject :: CanvasCaptureMediaStreamTrack -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CanvasCaptureMediaStreamTrack -> JSVal)
-> CanvasCaptureMediaStreamTrack
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasCaptureMediaStreamTrack -> JSVal
unCanvasCaptureMediaStreamTrack

instance IsMediaStreamTrack CanvasCaptureMediaStreamTrack
instance IsEventTarget CanvasCaptureMediaStreamTrack
instance IsGObject CanvasCaptureMediaStreamTrack where
  typeGType :: CanvasCaptureMediaStreamTrack -> JSM GType
typeGType CanvasCaptureMediaStreamTrack
_ = JSM GType
gTypeCanvasCaptureMediaStreamTrack
  {-# INLINE typeGType #-}

noCanvasCaptureMediaStreamTrack :: Maybe CanvasCaptureMediaStreamTrack
noCanvasCaptureMediaStreamTrack :: Maybe CanvasCaptureMediaStreamTrack
noCanvasCaptureMediaStreamTrack = Maybe CanvasCaptureMediaStreamTrack
forall a. Maybe a
Nothing
{-# INLINE noCanvasCaptureMediaStreamTrack #-}

gTypeCanvasCaptureMediaStreamTrack :: JSM GType
gTypeCanvasCaptureMediaStreamTrack :: JSM GType
gTypeCanvasCaptureMediaStreamTrack = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CanvasCaptureMediaStreamTrack"

-- | Functions for this inteface are in "JSDOM.CanvasGradient".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CanvasGradient Mozilla CanvasGradient documentation>
newtype CanvasGradient = CanvasGradient { CanvasGradient -> JSVal
unCanvasGradient :: JSVal }

instance PToJSVal CanvasGradient where
  pToJSVal :: CanvasGradient -> JSVal
pToJSVal = CanvasGradient -> JSVal
unCanvasGradient
  {-# INLINE pToJSVal #-}

instance PFromJSVal CanvasGradient where
  pFromJSVal :: JSVal -> CanvasGradient
pFromJSVal = JSVal -> CanvasGradient
CanvasGradient
  {-# INLINE pFromJSVal #-}

instance ToJSVal CanvasGradient where
  toJSVal :: CanvasGradient -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CanvasGradient -> JSVal) -> CanvasGradient -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasGradient -> JSVal
unCanvasGradient
  {-# INLINE toJSVal #-}

instance FromJSVal CanvasGradient where
  fromJSVal :: JSVal -> JSM (Maybe CanvasGradient)
fromJSVal JSVal
v = (JSVal -> CanvasGradient) -> Maybe JSVal -> Maybe CanvasGradient
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CanvasGradient
CanvasGradient (Maybe JSVal -> Maybe CanvasGradient)
-> JSM (Maybe JSVal) -> JSM (Maybe CanvasGradient)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CanvasGradient
fromJSValUnchecked = CanvasGradient -> JSM CanvasGradient
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CanvasGradient -> JSM CanvasGradient)
-> (JSVal -> CanvasGradient) -> JSVal -> JSM CanvasGradient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CanvasGradient
CanvasGradient
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CanvasGradient where
  makeObject :: CanvasGradient -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CanvasGradient -> JSVal) -> CanvasGradient -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasGradient -> JSVal
unCanvasGradient

instance IsGObject CanvasGradient where
  typeGType :: CanvasGradient -> JSM GType
typeGType CanvasGradient
_ = JSM GType
gTypeCanvasGradient
  {-# INLINE typeGType #-}

noCanvasGradient :: Maybe CanvasGradient
noCanvasGradient :: Maybe CanvasGradient
noCanvasGradient = Maybe CanvasGradient
forall a. Maybe a
Nothing
{-# INLINE noCanvasGradient #-}

gTypeCanvasGradient :: JSM GType
gTypeCanvasGradient :: JSM GType
gTypeCanvasGradient = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CanvasGradient"

-- | Functions for this inteface are in "JSDOM.CanvasPath".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CanvasPath Mozilla CanvasPath documentation>
newtype CanvasPath = CanvasPath { CanvasPath -> JSVal
unCanvasPath :: JSVal }

instance PToJSVal CanvasPath where
  pToJSVal :: CanvasPath -> JSVal
pToJSVal = CanvasPath -> JSVal
unCanvasPath
  {-# INLINE pToJSVal #-}

instance PFromJSVal CanvasPath where
  pFromJSVal :: JSVal -> CanvasPath
pFromJSVal = JSVal -> CanvasPath
CanvasPath
  {-# INLINE pFromJSVal #-}

instance ToJSVal CanvasPath where
  toJSVal :: CanvasPath -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CanvasPath -> JSVal) -> CanvasPath -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasPath -> JSVal
unCanvasPath
  {-# INLINE toJSVal #-}

instance FromJSVal CanvasPath where
  fromJSVal :: JSVal -> JSM (Maybe CanvasPath)
fromJSVal JSVal
v = (JSVal -> CanvasPath) -> Maybe JSVal -> Maybe CanvasPath
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CanvasPath
CanvasPath (Maybe JSVal -> Maybe CanvasPath)
-> JSM (Maybe JSVal) -> JSM (Maybe CanvasPath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CanvasPath
fromJSValUnchecked = CanvasPath -> JSM CanvasPath
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CanvasPath -> JSM CanvasPath)
-> (JSVal -> CanvasPath) -> JSVal -> JSM CanvasPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CanvasPath
CanvasPath
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CanvasPath where
  makeObject :: CanvasPath -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CanvasPath -> JSVal) -> CanvasPath -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasPath -> JSVal
unCanvasPath

class (IsGObject o) => IsCanvasPath o
toCanvasPath :: IsCanvasPath o => o -> CanvasPath
toCanvasPath :: forall o. IsCanvasPath o => o -> CanvasPath
toCanvasPath = JSVal -> CanvasPath
CanvasPath (JSVal -> CanvasPath) -> (o -> JSVal) -> o -> CanvasPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsCanvasPath CanvasPath
instance IsGObject CanvasPath where
  typeGType :: CanvasPath -> JSM GType
typeGType CanvasPath
_ = JSM GType
gTypeCanvasPath
  {-# INLINE typeGType #-}

noCanvasPath :: Maybe CanvasPath
noCanvasPath :: Maybe CanvasPath
noCanvasPath = Maybe CanvasPath
forall a. Maybe a
Nothing
{-# INLINE noCanvasPath #-}

gTypeCanvasPath :: JSM GType
gTypeCanvasPath :: JSM GType
gTypeCanvasPath = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CanvasPath"

-- | Functions for this inteface are in "JSDOM.CanvasPattern".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CanvasPattern Mozilla CanvasPattern documentation>
newtype CanvasPattern = CanvasPattern { CanvasPattern -> JSVal
unCanvasPattern :: JSVal }

instance PToJSVal CanvasPattern where
  pToJSVal :: CanvasPattern -> JSVal
pToJSVal = CanvasPattern -> JSVal
unCanvasPattern
  {-# INLINE pToJSVal #-}

instance PFromJSVal CanvasPattern where
  pFromJSVal :: JSVal -> CanvasPattern
pFromJSVal = JSVal -> CanvasPattern
CanvasPattern
  {-# INLINE pFromJSVal #-}

instance ToJSVal CanvasPattern where
  toJSVal :: CanvasPattern -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CanvasPattern -> JSVal) -> CanvasPattern -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasPattern -> JSVal
unCanvasPattern
  {-# INLINE toJSVal #-}

instance FromJSVal CanvasPattern where
  fromJSVal :: JSVal -> JSM (Maybe CanvasPattern)
fromJSVal JSVal
v = (JSVal -> CanvasPattern) -> Maybe JSVal -> Maybe CanvasPattern
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CanvasPattern
CanvasPattern (Maybe JSVal -> Maybe CanvasPattern)
-> JSM (Maybe JSVal) -> JSM (Maybe CanvasPattern)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CanvasPattern
fromJSValUnchecked = CanvasPattern -> JSM CanvasPattern
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CanvasPattern -> JSM CanvasPattern)
-> (JSVal -> CanvasPattern) -> JSVal -> JSM CanvasPattern
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CanvasPattern
CanvasPattern
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CanvasPattern where
  makeObject :: CanvasPattern -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CanvasPattern -> JSVal) -> CanvasPattern -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasPattern -> JSVal
unCanvasPattern

instance IsGObject CanvasPattern where
  typeGType :: CanvasPattern -> JSM GType
typeGType CanvasPattern
_ = JSM GType
gTypeCanvasPattern
  {-# INLINE typeGType #-}

noCanvasPattern :: Maybe CanvasPattern
noCanvasPattern :: Maybe CanvasPattern
noCanvasPattern = Maybe CanvasPattern
forall a. Maybe a
Nothing
{-# INLINE noCanvasPattern #-}

gTypeCanvasPattern :: JSM GType
gTypeCanvasPattern :: JSM GType
gTypeCanvasPattern = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CanvasPattern"

-- | Functions for this inteface are in "JSDOM.CanvasProxy".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CanvasProxy Mozilla CanvasProxy documentation>
newtype CanvasProxy = CanvasProxy { CanvasProxy -> JSVal
unCanvasProxy :: JSVal }

instance PToJSVal CanvasProxy where
  pToJSVal :: CanvasProxy -> JSVal
pToJSVal = CanvasProxy -> JSVal
unCanvasProxy
  {-# INLINE pToJSVal #-}

instance PFromJSVal CanvasProxy where
  pFromJSVal :: JSVal -> CanvasProxy
pFromJSVal = JSVal -> CanvasProxy
CanvasProxy
  {-# INLINE pFromJSVal #-}

instance ToJSVal CanvasProxy where
  toJSVal :: CanvasProxy -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CanvasProxy -> JSVal) -> CanvasProxy -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasProxy -> JSVal
unCanvasProxy
  {-# INLINE toJSVal #-}

instance FromJSVal CanvasProxy where
  fromJSVal :: JSVal -> JSM (Maybe CanvasProxy)
fromJSVal JSVal
v = (JSVal -> CanvasProxy) -> Maybe JSVal -> Maybe CanvasProxy
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CanvasProxy
CanvasProxy (Maybe JSVal -> Maybe CanvasProxy)
-> JSM (Maybe JSVal) -> JSM (Maybe CanvasProxy)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CanvasProxy
fromJSValUnchecked = CanvasProxy -> JSM CanvasProxy
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CanvasProxy -> JSM CanvasProxy)
-> (JSVal -> CanvasProxy) -> JSVal -> JSM CanvasProxy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CanvasProxy
CanvasProxy
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CanvasProxy where
  makeObject :: CanvasProxy -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CanvasProxy -> JSVal) -> CanvasProxy -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasProxy -> JSVal
unCanvasProxy

instance IsGObject CanvasProxy where
  typeGType :: CanvasProxy -> JSM GType
typeGType CanvasProxy
_ = JSM GType
gTypeCanvasProxy
  {-# INLINE typeGType #-}

noCanvasProxy :: Maybe CanvasProxy
noCanvasProxy :: Maybe CanvasProxy
noCanvasProxy = Maybe CanvasProxy
forall a. Maybe a
Nothing
{-# INLINE noCanvasProxy #-}

gTypeCanvasProxy :: JSM GType
gTypeCanvasProxy :: JSM GType
gTypeCanvasProxy = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CanvasProxy"

-- | Functions for this inteface are in "JSDOM.CanvasRenderingContext2D".
-- Base interface functions are in:
--
--     * "JSDOM.CanvasPath"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CanvasRenderingContext2D Mozilla CanvasRenderingContext2D documentation>
newtype CanvasRenderingContext2D = CanvasRenderingContext2D { CanvasRenderingContext2D -> JSVal
unCanvasRenderingContext2D :: JSVal }

instance PToJSVal CanvasRenderingContext2D where
  pToJSVal :: CanvasRenderingContext2D -> JSVal
pToJSVal = CanvasRenderingContext2D -> JSVal
unCanvasRenderingContext2D
  {-# INLINE pToJSVal #-}

instance PFromJSVal CanvasRenderingContext2D where
  pFromJSVal :: JSVal -> CanvasRenderingContext2D
pFromJSVal = JSVal -> CanvasRenderingContext2D
CanvasRenderingContext2D
  {-# INLINE pFromJSVal #-}

instance ToJSVal CanvasRenderingContext2D where
  toJSVal :: CanvasRenderingContext2D -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CanvasRenderingContext2D -> JSVal)
-> CanvasRenderingContext2D
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasRenderingContext2D -> JSVal
unCanvasRenderingContext2D
  {-# INLINE toJSVal #-}

instance FromJSVal CanvasRenderingContext2D where
  fromJSVal :: JSVal -> JSM (Maybe CanvasRenderingContext2D)
fromJSVal JSVal
v = (JSVal -> CanvasRenderingContext2D)
-> Maybe JSVal -> Maybe CanvasRenderingContext2D
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CanvasRenderingContext2D
CanvasRenderingContext2D (Maybe JSVal -> Maybe CanvasRenderingContext2D)
-> JSM (Maybe JSVal) -> JSM (Maybe CanvasRenderingContext2D)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CanvasRenderingContext2D
fromJSValUnchecked = CanvasRenderingContext2D -> JSM CanvasRenderingContext2D
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CanvasRenderingContext2D -> JSM CanvasRenderingContext2D)
-> (JSVal -> CanvasRenderingContext2D)
-> JSVal
-> JSM CanvasRenderingContext2D
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CanvasRenderingContext2D
CanvasRenderingContext2D
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CanvasRenderingContext2D where
  makeObject :: CanvasRenderingContext2D -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CanvasRenderingContext2D -> JSVal)
-> CanvasRenderingContext2D
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CanvasRenderingContext2D -> JSVal
unCanvasRenderingContext2D

instance IsCanvasPath CanvasRenderingContext2D
instance IsGObject CanvasRenderingContext2D where
  typeGType :: CanvasRenderingContext2D -> JSM GType
typeGType CanvasRenderingContext2D
_ = JSM GType
gTypeCanvasRenderingContext2D
  {-# INLINE typeGType #-}

noCanvasRenderingContext2D :: Maybe CanvasRenderingContext2D
noCanvasRenderingContext2D :: Maybe CanvasRenderingContext2D
noCanvasRenderingContext2D = Maybe CanvasRenderingContext2D
forall a. Maybe a
Nothing
{-# INLINE noCanvasRenderingContext2D #-}

gTypeCanvasRenderingContext2D :: JSM GType
gTypeCanvasRenderingContext2D :: JSM GType
gTypeCanvasRenderingContext2D = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CanvasRenderingContext2D"

-- | Functions for this inteface are in "JSDOM.ChannelMergerNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ChannelMergerNode Mozilla ChannelMergerNode documentation>
newtype ChannelMergerNode = ChannelMergerNode { ChannelMergerNode -> JSVal
unChannelMergerNode :: JSVal }

instance PToJSVal ChannelMergerNode where
  pToJSVal :: ChannelMergerNode -> JSVal
pToJSVal = ChannelMergerNode -> JSVal
unChannelMergerNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal ChannelMergerNode where
  pFromJSVal :: JSVal -> ChannelMergerNode
pFromJSVal = JSVal -> ChannelMergerNode
ChannelMergerNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal ChannelMergerNode where
  toJSVal :: ChannelMergerNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ChannelMergerNode -> JSVal) -> ChannelMergerNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ChannelMergerNode -> JSVal
unChannelMergerNode
  {-# INLINE toJSVal #-}

instance FromJSVal ChannelMergerNode where
  fromJSVal :: JSVal -> JSM (Maybe ChannelMergerNode)
fromJSVal JSVal
v = (JSVal -> ChannelMergerNode)
-> Maybe JSVal -> Maybe ChannelMergerNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ChannelMergerNode
ChannelMergerNode (Maybe JSVal -> Maybe ChannelMergerNode)
-> JSM (Maybe JSVal) -> JSM (Maybe ChannelMergerNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ChannelMergerNode
fromJSValUnchecked = ChannelMergerNode -> JSM ChannelMergerNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ChannelMergerNode -> JSM ChannelMergerNode)
-> (JSVal -> ChannelMergerNode) -> JSVal -> JSM ChannelMergerNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ChannelMergerNode
ChannelMergerNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ChannelMergerNode where
  makeObject :: ChannelMergerNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ChannelMergerNode -> JSVal) -> ChannelMergerNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ChannelMergerNode -> JSVal
unChannelMergerNode

instance IsAudioNode ChannelMergerNode
instance IsEventTarget ChannelMergerNode
instance IsGObject ChannelMergerNode where
  typeGType :: ChannelMergerNode -> JSM GType
typeGType ChannelMergerNode
_ = JSM GType
gTypeChannelMergerNode
  {-# INLINE typeGType #-}

noChannelMergerNode :: Maybe ChannelMergerNode
noChannelMergerNode :: Maybe ChannelMergerNode
noChannelMergerNode = Maybe ChannelMergerNode
forall a. Maybe a
Nothing
{-# INLINE noChannelMergerNode #-}

gTypeChannelMergerNode :: JSM GType
gTypeChannelMergerNode :: JSM GType
gTypeChannelMergerNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ChannelMergerNode"

-- | Functions for this inteface are in "JSDOM.ChannelSplitterNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ChannelSplitterNode Mozilla ChannelSplitterNode documentation>
newtype ChannelSplitterNode = ChannelSplitterNode { ChannelSplitterNode -> JSVal
unChannelSplitterNode :: JSVal }

instance PToJSVal ChannelSplitterNode where
  pToJSVal :: ChannelSplitterNode -> JSVal
pToJSVal = ChannelSplitterNode -> JSVal
unChannelSplitterNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal ChannelSplitterNode where
  pFromJSVal :: JSVal -> ChannelSplitterNode
pFromJSVal = JSVal -> ChannelSplitterNode
ChannelSplitterNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal ChannelSplitterNode where
  toJSVal :: ChannelSplitterNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ChannelSplitterNode -> JSVal)
-> ChannelSplitterNode
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ChannelSplitterNode -> JSVal
unChannelSplitterNode
  {-# INLINE toJSVal #-}

instance FromJSVal ChannelSplitterNode where
  fromJSVal :: JSVal -> JSM (Maybe ChannelSplitterNode)
fromJSVal JSVal
v = (JSVal -> ChannelSplitterNode)
-> Maybe JSVal -> Maybe ChannelSplitterNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ChannelSplitterNode
ChannelSplitterNode (Maybe JSVal -> Maybe ChannelSplitterNode)
-> JSM (Maybe JSVal) -> JSM (Maybe ChannelSplitterNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ChannelSplitterNode
fromJSValUnchecked = ChannelSplitterNode -> JSM ChannelSplitterNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ChannelSplitterNode -> JSM ChannelSplitterNode)
-> (JSVal -> ChannelSplitterNode)
-> JSVal
-> JSM ChannelSplitterNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ChannelSplitterNode
ChannelSplitterNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ChannelSplitterNode where
  makeObject :: ChannelSplitterNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ChannelSplitterNode -> JSVal)
-> ChannelSplitterNode
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ChannelSplitterNode -> JSVal
unChannelSplitterNode

instance IsAudioNode ChannelSplitterNode
instance IsEventTarget ChannelSplitterNode
instance IsGObject ChannelSplitterNode where
  typeGType :: ChannelSplitterNode -> JSM GType
typeGType ChannelSplitterNode
_ = JSM GType
gTypeChannelSplitterNode
  {-# INLINE typeGType #-}

noChannelSplitterNode :: Maybe ChannelSplitterNode
noChannelSplitterNode :: Maybe ChannelSplitterNode
noChannelSplitterNode = Maybe ChannelSplitterNode
forall a. Maybe a
Nothing
{-# INLINE noChannelSplitterNode #-}

gTypeChannelSplitterNode :: JSM GType
gTypeChannelSplitterNode :: JSM GType
gTypeChannelSplitterNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ChannelSplitterNode"

-- | Functions for this inteface are in "JSDOM.CharacterData".
-- Base interface functions are in:
--
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.ChildNode"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CharacterData Mozilla CharacterData documentation>
newtype CharacterData = CharacterData { CharacterData -> JSVal
unCharacterData :: JSVal }

instance PToJSVal CharacterData where
  pToJSVal :: CharacterData -> JSVal
pToJSVal = CharacterData -> JSVal
unCharacterData
  {-# INLINE pToJSVal #-}

instance PFromJSVal CharacterData where
  pFromJSVal :: JSVal -> CharacterData
pFromJSVal = JSVal -> CharacterData
CharacterData
  {-# INLINE pFromJSVal #-}

instance ToJSVal CharacterData where
  toJSVal :: CharacterData -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CharacterData -> JSVal) -> CharacterData -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CharacterData -> JSVal
unCharacterData
  {-# INLINE toJSVal #-}

instance FromJSVal CharacterData where
  fromJSVal :: JSVal -> JSM (Maybe CharacterData)
fromJSVal JSVal
v = (JSVal -> CharacterData) -> Maybe JSVal -> Maybe CharacterData
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CharacterData
CharacterData (Maybe JSVal -> Maybe CharacterData)
-> JSM (Maybe JSVal) -> JSM (Maybe CharacterData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CharacterData
fromJSValUnchecked = CharacterData -> JSM CharacterData
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CharacterData -> JSM CharacterData)
-> (JSVal -> CharacterData) -> JSVal -> JSM CharacterData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CharacterData
CharacterData
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CharacterData where
  makeObject :: CharacterData -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CharacterData -> JSVal) -> CharacterData -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CharacterData -> JSVal
unCharacterData

class (IsNode o, IsEventTarget o, IsNonDocumentTypeChildNode o, IsChildNode o, IsGObject o) => IsCharacterData o
toCharacterData :: IsCharacterData o => o -> CharacterData
toCharacterData :: forall o. IsCharacterData o => o -> CharacterData
toCharacterData = JSVal -> CharacterData
CharacterData (JSVal -> CharacterData) -> (o -> JSVal) -> o -> CharacterData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsCharacterData CharacterData
instance IsNode CharacterData
instance IsEventTarget CharacterData
instance IsNonDocumentTypeChildNode CharacterData
instance IsChildNode CharacterData
instance IsGObject CharacterData where
  typeGType :: CharacterData -> JSM GType
typeGType CharacterData
_ = JSM GType
gTypeCharacterData
  {-# INLINE typeGType #-}

noCharacterData :: Maybe CharacterData
noCharacterData :: Maybe CharacterData
noCharacterData = Maybe CharacterData
forall a. Maybe a
Nothing
{-# INLINE noCharacterData #-}

gTypeCharacterData :: JSM GType
gTypeCharacterData :: JSM GType
gTypeCharacterData = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CharacterData"

-- | Functions for this inteface are in "JSDOM.ChildNode".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ChildNode Mozilla ChildNode documentation>
newtype ChildNode = ChildNode { ChildNode -> JSVal
unChildNode :: JSVal }

instance PToJSVal ChildNode where
  pToJSVal :: ChildNode -> JSVal
pToJSVal = ChildNode -> JSVal
unChildNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal ChildNode where
  pFromJSVal :: JSVal -> ChildNode
pFromJSVal = JSVal -> ChildNode
ChildNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal ChildNode where
  toJSVal :: ChildNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ChildNode -> JSVal) -> ChildNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ChildNode -> JSVal
unChildNode
  {-# INLINE toJSVal #-}

instance FromJSVal ChildNode where
  fromJSVal :: JSVal -> JSM (Maybe ChildNode)
fromJSVal JSVal
v = (JSVal -> ChildNode) -> Maybe JSVal -> Maybe ChildNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ChildNode
ChildNode (Maybe JSVal -> Maybe ChildNode)
-> JSM (Maybe JSVal) -> JSM (Maybe ChildNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ChildNode
fromJSValUnchecked = ChildNode -> JSM ChildNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ChildNode -> JSM ChildNode)
-> (JSVal -> ChildNode) -> JSVal -> JSM ChildNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ChildNode
ChildNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ChildNode where
  makeObject :: ChildNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ChildNode -> JSVal) -> ChildNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ChildNode -> JSVal
unChildNode

class (IsGObject o) => IsChildNode o
toChildNode :: IsChildNode o => o -> ChildNode
toChildNode :: forall o. IsChildNode o => o -> ChildNode
toChildNode = JSVal -> ChildNode
ChildNode (JSVal -> ChildNode) -> (o -> JSVal) -> o -> ChildNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsChildNode ChildNode
instance IsGObject ChildNode where
  typeGType :: ChildNode -> JSM GType
typeGType ChildNode
_ = JSM GType
gTypeChildNode
  {-# INLINE typeGType #-}

noChildNode :: Maybe ChildNode
noChildNode :: Maybe ChildNode
noChildNode = Maybe ChildNode
forall a. Maybe a
Nothing
{-# INLINE noChildNode #-}

gTypeChildNode :: JSM GType
gTypeChildNode :: JSM GType
gTypeChildNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ChildNode"

-- | Functions for this inteface are in "JSDOM.ClipboardEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ClipboardEvent Mozilla ClipboardEvent documentation>
newtype ClipboardEvent = ClipboardEvent { ClipboardEvent -> JSVal
unClipboardEvent :: JSVal }

instance PToJSVal ClipboardEvent where
  pToJSVal :: ClipboardEvent -> JSVal
pToJSVal = ClipboardEvent -> JSVal
unClipboardEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal ClipboardEvent where
  pFromJSVal :: JSVal -> ClipboardEvent
pFromJSVal = JSVal -> ClipboardEvent
ClipboardEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal ClipboardEvent where
  toJSVal :: ClipboardEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ClipboardEvent -> JSVal) -> ClipboardEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ClipboardEvent -> JSVal
unClipboardEvent
  {-# INLINE toJSVal #-}

instance FromJSVal ClipboardEvent where
  fromJSVal :: JSVal -> JSM (Maybe ClipboardEvent)
fromJSVal JSVal
v = (JSVal -> ClipboardEvent) -> Maybe JSVal -> Maybe ClipboardEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ClipboardEvent
ClipboardEvent (Maybe JSVal -> Maybe ClipboardEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe ClipboardEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ClipboardEvent
fromJSValUnchecked = ClipboardEvent -> JSM ClipboardEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ClipboardEvent -> JSM ClipboardEvent)
-> (JSVal -> ClipboardEvent) -> JSVal -> JSM ClipboardEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ClipboardEvent
ClipboardEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ClipboardEvent where
  makeObject :: ClipboardEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ClipboardEvent -> JSVal) -> ClipboardEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ClipboardEvent -> JSVal
unClipboardEvent

instance IsEvent ClipboardEvent
instance IsGObject ClipboardEvent where
  typeGType :: ClipboardEvent -> JSM GType
typeGType ClipboardEvent
_ = JSM GType
gTypeClipboardEvent
  {-# INLINE typeGType #-}

noClipboardEvent :: Maybe ClipboardEvent
noClipboardEvent :: Maybe ClipboardEvent
noClipboardEvent = Maybe ClipboardEvent
forall a. Maybe a
Nothing
{-# INLINE noClipboardEvent #-}

gTypeClipboardEvent :: JSM GType
gTypeClipboardEvent :: JSM GType
gTypeClipboardEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ClipboardEvent"

-- | Functions for this inteface are in "JSDOM.ClipboardEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ClipboardEventInit Mozilla ClipboardEventInit documentation>
newtype ClipboardEventInit = ClipboardEventInit { ClipboardEventInit -> JSVal
unClipboardEventInit :: JSVal }

instance PToJSVal ClipboardEventInit where
  pToJSVal :: ClipboardEventInit -> JSVal
pToJSVal = ClipboardEventInit -> JSVal
unClipboardEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal ClipboardEventInit where
  pFromJSVal :: JSVal -> ClipboardEventInit
pFromJSVal = JSVal -> ClipboardEventInit
ClipboardEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal ClipboardEventInit where
  toJSVal :: ClipboardEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ClipboardEventInit -> JSVal) -> ClipboardEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ClipboardEventInit -> JSVal
unClipboardEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal ClipboardEventInit where
  fromJSVal :: JSVal -> JSM (Maybe ClipboardEventInit)
fromJSVal JSVal
v = (JSVal -> ClipboardEventInit)
-> Maybe JSVal -> Maybe ClipboardEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ClipboardEventInit
ClipboardEventInit (Maybe JSVal -> Maybe ClipboardEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe ClipboardEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ClipboardEventInit
fromJSValUnchecked = ClipboardEventInit -> JSM ClipboardEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ClipboardEventInit -> JSM ClipboardEventInit)
-> (JSVal -> ClipboardEventInit) -> JSVal -> JSM ClipboardEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ClipboardEventInit
ClipboardEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ClipboardEventInit where
  makeObject :: ClipboardEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ClipboardEventInit -> JSVal)
-> ClipboardEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ClipboardEventInit -> JSVal
unClipboardEventInit

instance IsEventInit ClipboardEventInit
instance IsGObject ClipboardEventInit where
  typeGType :: ClipboardEventInit -> JSM GType
typeGType ClipboardEventInit
_ = JSM GType
gTypeClipboardEventInit
  {-# INLINE typeGType #-}

noClipboardEventInit :: Maybe ClipboardEventInit
noClipboardEventInit :: Maybe ClipboardEventInit
noClipboardEventInit = Maybe ClipboardEventInit
forall a. Maybe a
Nothing
{-# INLINE noClipboardEventInit #-}

gTypeClipboardEventInit :: JSM GType
gTypeClipboardEventInit :: JSM GType
gTypeClipboardEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ClipboardEventInit"

-- | Functions for this inteface are in "JSDOM.CloseEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CloseEvent Mozilla CloseEvent documentation>
newtype CloseEvent = CloseEvent { CloseEvent -> JSVal
unCloseEvent :: JSVal }

instance PToJSVal CloseEvent where
  pToJSVal :: CloseEvent -> JSVal
pToJSVal = CloseEvent -> JSVal
unCloseEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal CloseEvent where
  pFromJSVal :: JSVal -> CloseEvent
pFromJSVal = JSVal -> CloseEvent
CloseEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal CloseEvent where
  toJSVal :: CloseEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CloseEvent -> JSVal) -> CloseEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CloseEvent -> JSVal
unCloseEvent
  {-# INLINE toJSVal #-}

instance FromJSVal CloseEvent where
  fromJSVal :: JSVal -> JSM (Maybe CloseEvent)
fromJSVal JSVal
v = (JSVal -> CloseEvent) -> Maybe JSVal -> Maybe CloseEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CloseEvent
CloseEvent (Maybe JSVal -> Maybe CloseEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe CloseEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CloseEvent
fromJSValUnchecked = CloseEvent -> JSM CloseEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CloseEvent -> JSM CloseEvent)
-> (JSVal -> CloseEvent) -> JSVal -> JSM CloseEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CloseEvent
CloseEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CloseEvent where
  makeObject :: CloseEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CloseEvent -> JSVal) -> CloseEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CloseEvent -> JSVal
unCloseEvent

instance IsEvent CloseEvent
instance IsGObject CloseEvent where
  typeGType :: CloseEvent -> JSM GType
typeGType CloseEvent
_ = JSM GType
gTypeCloseEvent
  {-# INLINE typeGType #-}

noCloseEvent :: Maybe CloseEvent
noCloseEvent :: Maybe CloseEvent
noCloseEvent = Maybe CloseEvent
forall a. Maybe a
Nothing
{-# INLINE noCloseEvent #-}

gTypeCloseEvent :: JSM GType
gTypeCloseEvent :: JSM GType
gTypeCloseEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CloseEvent"

-- | Functions for this inteface are in "JSDOM.CloseEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CloseEventInit Mozilla CloseEventInit documentation>
newtype CloseEventInit = CloseEventInit { CloseEventInit -> JSVal
unCloseEventInit :: JSVal }

instance PToJSVal CloseEventInit where
  pToJSVal :: CloseEventInit -> JSVal
pToJSVal = CloseEventInit -> JSVal
unCloseEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal CloseEventInit where
  pFromJSVal :: JSVal -> CloseEventInit
pFromJSVal = JSVal -> CloseEventInit
CloseEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal CloseEventInit where
  toJSVal :: CloseEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CloseEventInit -> JSVal) -> CloseEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CloseEventInit -> JSVal
unCloseEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal CloseEventInit where
  fromJSVal :: JSVal -> JSM (Maybe CloseEventInit)
fromJSVal JSVal
v = (JSVal -> CloseEventInit) -> Maybe JSVal -> Maybe CloseEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CloseEventInit
CloseEventInit (Maybe JSVal -> Maybe CloseEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe CloseEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CloseEventInit
fromJSValUnchecked = CloseEventInit -> JSM CloseEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CloseEventInit -> JSM CloseEventInit)
-> (JSVal -> CloseEventInit) -> JSVal -> JSM CloseEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CloseEventInit
CloseEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CloseEventInit where
  makeObject :: CloseEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CloseEventInit -> JSVal) -> CloseEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CloseEventInit -> JSVal
unCloseEventInit

instance IsEventInit CloseEventInit
instance IsGObject CloseEventInit where
  typeGType :: CloseEventInit -> JSM GType
typeGType CloseEventInit
_ = JSM GType
gTypeCloseEventInit
  {-# INLINE typeGType #-}

noCloseEventInit :: Maybe CloseEventInit
noCloseEventInit :: Maybe CloseEventInit
noCloseEventInit = Maybe CloseEventInit
forall a. Maybe a
Nothing
{-# INLINE noCloseEventInit #-}

gTypeCloseEventInit :: JSM GType
gTypeCloseEventInit :: JSM GType
gTypeCloseEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CloseEventInit"

-- | Functions for this inteface are in "JSDOM.CommandLineAPIHost".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CommandLineAPIHost Mozilla CommandLineAPIHost documentation>
newtype CommandLineAPIHost = CommandLineAPIHost { CommandLineAPIHost -> JSVal
unCommandLineAPIHost :: JSVal }

instance PToJSVal CommandLineAPIHost where
  pToJSVal :: CommandLineAPIHost -> JSVal
pToJSVal = CommandLineAPIHost -> JSVal
unCommandLineAPIHost
  {-# INLINE pToJSVal #-}

instance PFromJSVal CommandLineAPIHost where
  pFromJSVal :: JSVal -> CommandLineAPIHost
pFromJSVal = JSVal -> CommandLineAPIHost
CommandLineAPIHost
  {-# INLINE pFromJSVal #-}

instance ToJSVal CommandLineAPIHost where
  toJSVal :: CommandLineAPIHost -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CommandLineAPIHost -> JSVal) -> CommandLineAPIHost -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommandLineAPIHost -> JSVal
unCommandLineAPIHost
  {-# INLINE toJSVal #-}

instance FromJSVal CommandLineAPIHost where
  fromJSVal :: JSVal -> JSM (Maybe CommandLineAPIHost)
fromJSVal JSVal
v = (JSVal -> CommandLineAPIHost)
-> Maybe JSVal -> Maybe CommandLineAPIHost
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CommandLineAPIHost
CommandLineAPIHost (Maybe JSVal -> Maybe CommandLineAPIHost)
-> JSM (Maybe JSVal) -> JSM (Maybe CommandLineAPIHost)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CommandLineAPIHost
fromJSValUnchecked = CommandLineAPIHost -> JSM CommandLineAPIHost
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CommandLineAPIHost -> JSM CommandLineAPIHost)
-> (JSVal -> CommandLineAPIHost) -> JSVal -> JSM CommandLineAPIHost
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CommandLineAPIHost
CommandLineAPIHost
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CommandLineAPIHost where
  makeObject :: CommandLineAPIHost -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CommandLineAPIHost -> JSVal)
-> CommandLineAPIHost
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommandLineAPIHost -> JSVal
unCommandLineAPIHost

instance IsGObject CommandLineAPIHost where
  typeGType :: CommandLineAPIHost -> JSM GType
typeGType CommandLineAPIHost
_ = JSM GType
gTypeCommandLineAPIHost
  {-# INLINE typeGType #-}

noCommandLineAPIHost :: Maybe CommandLineAPIHost
noCommandLineAPIHost :: Maybe CommandLineAPIHost
noCommandLineAPIHost = Maybe CommandLineAPIHost
forall a. Maybe a
Nothing
{-# INLINE noCommandLineAPIHost #-}

gTypeCommandLineAPIHost :: JSM GType
gTypeCommandLineAPIHost :: JSM GType
gTypeCommandLineAPIHost = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CommandLineAPIHost"

-- | Functions for this inteface are in "JSDOM.Comment".
-- Base interface functions are in:
--
--     * "JSDOM.CharacterData"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.ChildNode"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Comment Mozilla Comment documentation>
newtype Comment = Comment { Comment -> JSVal
unComment :: JSVal }

instance PToJSVal Comment where
  pToJSVal :: Comment -> JSVal
pToJSVal = Comment -> JSVal
unComment
  {-# INLINE pToJSVal #-}

instance PFromJSVal Comment where
  pFromJSVal :: JSVal -> Comment
pFromJSVal = JSVal -> Comment
Comment
  {-# INLINE pFromJSVal #-}

instance ToJSVal Comment where
  toJSVal :: Comment -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Comment -> JSVal) -> Comment -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Comment -> JSVal
unComment
  {-# INLINE toJSVal #-}

instance FromJSVal Comment where
  fromJSVal :: JSVal -> JSM (Maybe Comment)
fromJSVal JSVal
v = (JSVal -> Comment) -> Maybe JSVal -> Maybe Comment
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Comment
Comment (Maybe JSVal -> Maybe Comment)
-> JSM (Maybe JSVal) -> JSM (Maybe Comment)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Comment
fromJSValUnchecked = Comment -> JSM Comment
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Comment -> JSM Comment)
-> (JSVal -> Comment) -> JSVal -> JSM Comment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Comment
Comment
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Comment where
  makeObject :: Comment -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Comment -> JSVal) -> Comment -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Comment -> JSVal
unComment

instance IsCharacterData Comment
instance IsNode Comment
instance IsEventTarget Comment
instance IsNonDocumentTypeChildNode Comment
instance IsChildNode Comment
instance IsGObject Comment where
  typeGType :: Comment -> JSM GType
typeGType Comment
_ = JSM GType
gTypeComment
  {-# INLINE typeGType #-}

noComment :: Maybe Comment
noComment :: Maybe Comment
noComment = Maybe Comment
forall a. Maybe a
Nothing
{-# INLINE noComment #-}

gTypeComment :: JSM GType
gTypeComment :: JSM GType
gTypeComment = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Comment"

-- | Functions for this inteface are in "JSDOM.CompositionEvent".
-- Base interface functions are in:
--
--     * "JSDOM.UIEvent"
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CompositionEvent Mozilla CompositionEvent documentation>
newtype CompositionEvent = CompositionEvent { CompositionEvent -> JSVal
unCompositionEvent :: JSVal }

instance PToJSVal CompositionEvent where
  pToJSVal :: CompositionEvent -> JSVal
pToJSVal = CompositionEvent -> JSVal
unCompositionEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal CompositionEvent where
  pFromJSVal :: JSVal -> CompositionEvent
pFromJSVal = JSVal -> CompositionEvent
CompositionEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal CompositionEvent where
  toJSVal :: CompositionEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CompositionEvent -> JSVal) -> CompositionEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompositionEvent -> JSVal
unCompositionEvent
  {-# INLINE toJSVal #-}

instance FromJSVal CompositionEvent where
  fromJSVal :: JSVal -> JSM (Maybe CompositionEvent)
fromJSVal JSVal
v = (JSVal -> CompositionEvent)
-> Maybe JSVal -> Maybe CompositionEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CompositionEvent
CompositionEvent (Maybe JSVal -> Maybe CompositionEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe CompositionEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CompositionEvent
fromJSValUnchecked = CompositionEvent -> JSM CompositionEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CompositionEvent -> JSM CompositionEvent)
-> (JSVal -> CompositionEvent) -> JSVal -> JSM CompositionEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CompositionEvent
CompositionEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CompositionEvent where
  makeObject :: CompositionEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CompositionEvent -> JSVal) -> CompositionEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompositionEvent -> JSVal
unCompositionEvent

instance IsUIEvent CompositionEvent
instance IsEvent CompositionEvent
instance IsGObject CompositionEvent where
  typeGType :: CompositionEvent -> JSM GType
typeGType CompositionEvent
_ = JSM GType
gTypeCompositionEvent
  {-# INLINE typeGType #-}

noCompositionEvent :: Maybe CompositionEvent
noCompositionEvent :: Maybe CompositionEvent
noCompositionEvent = Maybe CompositionEvent
forall a. Maybe a
Nothing
{-# INLINE noCompositionEvent #-}

gTypeCompositionEvent :: JSM GType
gTypeCompositionEvent :: JSM GType
gTypeCompositionEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CompositionEvent"

-- | Functions for this inteface are in "JSDOM.CompositionEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.UIEventInit"
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CompositionEventInit Mozilla CompositionEventInit documentation>
newtype CompositionEventInit = CompositionEventInit { CompositionEventInit -> JSVal
unCompositionEventInit :: JSVal }

instance PToJSVal CompositionEventInit where
  pToJSVal :: CompositionEventInit -> JSVal
pToJSVal = CompositionEventInit -> JSVal
unCompositionEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal CompositionEventInit where
  pFromJSVal :: JSVal -> CompositionEventInit
pFromJSVal = JSVal -> CompositionEventInit
CompositionEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal CompositionEventInit where
  toJSVal :: CompositionEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CompositionEventInit -> JSVal)
-> CompositionEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompositionEventInit -> JSVal
unCompositionEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal CompositionEventInit where
  fromJSVal :: JSVal -> JSM (Maybe CompositionEventInit)
fromJSVal JSVal
v = (JSVal -> CompositionEventInit)
-> Maybe JSVal -> Maybe CompositionEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CompositionEventInit
CompositionEventInit (Maybe JSVal -> Maybe CompositionEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe CompositionEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CompositionEventInit
fromJSValUnchecked = CompositionEventInit -> JSM CompositionEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CompositionEventInit -> JSM CompositionEventInit)
-> (JSVal -> CompositionEventInit)
-> JSVal
-> JSM CompositionEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CompositionEventInit
CompositionEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CompositionEventInit where
  makeObject :: CompositionEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CompositionEventInit -> JSVal)
-> CompositionEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompositionEventInit -> JSVal
unCompositionEventInit

instance IsUIEventInit CompositionEventInit
instance IsEventInit CompositionEventInit
instance IsGObject CompositionEventInit where
  typeGType :: CompositionEventInit -> JSM GType
typeGType CompositionEventInit
_ = JSM GType
gTypeCompositionEventInit
  {-# INLINE typeGType #-}

noCompositionEventInit :: Maybe CompositionEventInit
noCompositionEventInit :: Maybe CompositionEventInit
noCompositionEventInit = Maybe CompositionEventInit
forall a. Maybe a
Nothing
{-# INLINE noCompositionEventInit #-}

gTypeCompositionEventInit :: JSM GType
gTypeCompositionEventInit :: JSM GType
gTypeCompositionEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CompositionEventInit"

-- | Functions for this inteface are in "JSDOM.ConstrainBooleanParameters".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ConstrainBooleanParameters Mozilla ConstrainBooleanParameters documentation>
newtype ConstrainBooleanParameters = ConstrainBooleanParameters { ConstrainBooleanParameters -> JSVal
unConstrainBooleanParameters :: JSVal }

instance PToJSVal ConstrainBooleanParameters where
  pToJSVal :: ConstrainBooleanParameters -> JSVal
pToJSVal = ConstrainBooleanParameters -> JSVal
unConstrainBooleanParameters
  {-# INLINE pToJSVal #-}

instance PFromJSVal ConstrainBooleanParameters where
  pFromJSVal :: JSVal -> ConstrainBooleanParameters
pFromJSVal = JSVal -> ConstrainBooleanParameters
ConstrainBooleanParameters
  {-# INLINE pFromJSVal #-}

instance ToJSVal ConstrainBooleanParameters where
  toJSVal :: ConstrainBooleanParameters -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ConstrainBooleanParameters -> JSVal)
-> ConstrainBooleanParameters
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstrainBooleanParameters -> JSVal
unConstrainBooleanParameters
  {-# INLINE toJSVal #-}

instance FromJSVal ConstrainBooleanParameters where
  fromJSVal :: JSVal -> JSM (Maybe ConstrainBooleanParameters)
fromJSVal JSVal
v = (JSVal -> ConstrainBooleanParameters)
-> Maybe JSVal -> Maybe ConstrainBooleanParameters
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ConstrainBooleanParameters
ConstrainBooleanParameters (Maybe JSVal -> Maybe ConstrainBooleanParameters)
-> JSM (Maybe JSVal) -> JSM (Maybe ConstrainBooleanParameters)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ConstrainBooleanParameters
fromJSValUnchecked = ConstrainBooleanParameters -> JSM ConstrainBooleanParameters
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ConstrainBooleanParameters -> JSM ConstrainBooleanParameters)
-> (JSVal -> ConstrainBooleanParameters)
-> JSVal
-> JSM ConstrainBooleanParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ConstrainBooleanParameters
ConstrainBooleanParameters
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ConstrainBooleanParameters where
  makeObject :: ConstrainBooleanParameters -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ConstrainBooleanParameters -> JSVal)
-> ConstrainBooleanParameters
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstrainBooleanParameters -> JSVal
unConstrainBooleanParameters

instance IsGObject ConstrainBooleanParameters where
  typeGType :: ConstrainBooleanParameters -> JSM GType
typeGType ConstrainBooleanParameters
_ = JSM GType
gTypeConstrainBooleanParameters
  {-# INLINE typeGType #-}

noConstrainBooleanParameters :: Maybe ConstrainBooleanParameters
noConstrainBooleanParameters :: Maybe ConstrainBooleanParameters
noConstrainBooleanParameters = Maybe ConstrainBooleanParameters
forall a. Maybe a
Nothing
{-# INLINE noConstrainBooleanParameters #-}

gTypeConstrainBooleanParameters :: JSM GType
gTypeConstrainBooleanParameters :: JSM GType
gTypeConstrainBooleanParameters = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ConstrainBooleanParameters"

-- | Functions for this inteface are in "JSDOM.ConstrainDOMStringParameters".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ConstrainDOMStringParameters Mozilla ConstrainDOMStringParameters documentation>
newtype ConstrainDOMStringParameters = ConstrainDOMStringParameters { ConstrainDOMStringParameters -> JSVal
unConstrainDOMStringParameters :: JSVal }

instance PToJSVal ConstrainDOMStringParameters where
  pToJSVal :: ConstrainDOMStringParameters -> JSVal
pToJSVal = ConstrainDOMStringParameters -> JSVal
unConstrainDOMStringParameters
  {-# INLINE pToJSVal #-}

instance PFromJSVal ConstrainDOMStringParameters where
  pFromJSVal :: JSVal -> ConstrainDOMStringParameters
pFromJSVal = JSVal -> ConstrainDOMStringParameters
ConstrainDOMStringParameters
  {-# INLINE pFromJSVal #-}

instance ToJSVal ConstrainDOMStringParameters where
  toJSVal :: ConstrainDOMStringParameters -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ConstrainDOMStringParameters -> JSVal)
-> ConstrainDOMStringParameters
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstrainDOMStringParameters -> JSVal
unConstrainDOMStringParameters
  {-# INLINE toJSVal #-}

instance FromJSVal ConstrainDOMStringParameters where
  fromJSVal :: JSVal -> JSM (Maybe ConstrainDOMStringParameters)
fromJSVal JSVal
v = (JSVal -> ConstrainDOMStringParameters)
-> Maybe JSVal -> Maybe ConstrainDOMStringParameters
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ConstrainDOMStringParameters
ConstrainDOMStringParameters (Maybe JSVal -> Maybe ConstrainDOMStringParameters)
-> JSM (Maybe JSVal) -> JSM (Maybe ConstrainDOMStringParameters)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ConstrainDOMStringParameters
fromJSValUnchecked = ConstrainDOMStringParameters -> JSM ConstrainDOMStringParameters
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ConstrainDOMStringParameters -> JSM ConstrainDOMStringParameters)
-> (JSVal -> ConstrainDOMStringParameters)
-> JSVal
-> JSM ConstrainDOMStringParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ConstrainDOMStringParameters
ConstrainDOMStringParameters
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ConstrainDOMStringParameters where
  makeObject :: ConstrainDOMStringParameters -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ConstrainDOMStringParameters -> JSVal)
-> ConstrainDOMStringParameters
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstrainDOMStringParameters -> JSVal
unConstrainDOMStringParameters

instance IsGObject ConstrainDOMStringParameters where
  typeGType :: ConstrainDOMStringParameters -> JSM GType
typeGType ConstrainDOMStringParameters
_ = JSM GType
gTypeConstrainDOMStringParameters
  {-# INLINE typeGType #-}

noConstrainDOMStringParameters :: Maybe ConstrainDOMStringParameters
noConstrainDOMStringParameters :: Maybe ConstrainDOMStringParameters
noConstrainDOMStringParameters = Maybe ConstrainDOMStringParameters
forall a. Maybe a
Nothing
{-# INLINE noConstrainDOMStringParameters #-}

gTypeConstrainDOMStringParameters :: JSM GType
gTypeConstrainDOMStringParameters :: JSM GType
gTypeConstrainDOMStringParameters = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ConstrainDOMStringParameters"

-- | Functions for this inteface are in "JSDOM.ConstrainDoubleRange".
-- Base interface functions are in:
--
--     * "JSDOM.DoubleRange"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ConstrainDoubleRange Mozilla ConstrainDoubleRange documentation>
newtype ConstrainDoubleRange = ConstrainDoubleRange { ConstrainDoubleRange -> JSVal
unConstrainDoubleRange :: JSVal }

instance PToJSVal ConstrainDoubleRange where
  pToJSVal :: ConstrainDoubleRange -> JSVal
pToJSVal = ConstrainDoubleRange -> JSVal
unConstrainDoubleRange
  {-# INLINE pToJSVal #-}

instance PFromJSVal ConstrainDoubleRange where
  pFromJSVal :: JSVal -> ConstrainDoubleRange
pFromJSVal = JSVal -> ConstrainDoubleRange
ConstrainDoubleRange
  {-# INLINE pFromJSVal #-}

instance ToJSVal ConstrainDoubleRange where
  toJSVal :: ConstrainDoubleRange -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ConstrainDoubleRange -> JSVal)
-> ConstrainDoubleRange
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstrainDoubleRange -> JSVal
unConstrainDoubleRange
  {-# INLINE toJSVal #-}

instance FromJSVal ConstrainDoubleRange where
  fromJSVal :: JSVal -> JSM (Maybe ConstrainDoubleRange)
fromJSVal JSVal
v = (JSVal -> ConstrainDoubleRange)
-> Maybe JSVal -> Maybe ConstrainDoubleRange
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ConstrainDoubleRange
ConstrainDoubleRange (Maybe JSVal -> Maybe ConstrainDoubleRange)
-> JSM (Maybe JSVal) -> JSM (Maybe ConstrainDoubleRange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ConstrainDoubleRange
fromJSValUnchecked = ConstrainDoubleRange -> JSM ConstrainDoubleRange
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ConstrainDoubleRange -> JSM ConstrainDoubleRange)
-> (JSVal -> ConstrainDoubleRange)
-> JSVal
-> JSM ConstrainDoubleRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ConstrainDoubleRange
ConstrainDoubleRange
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ConstrainDoubleRange where
  makeObject :: ConstrainDoubleRange -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ConstrainDoubleRange -> JSVal)
-> ConstrainDoubleRange
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstrainDoubleRange -> JSVal
unConstrainDoubleRange

instance IsDoubleRange ConstrainDoubleRange
instance IsGObject ConstrainDoubleRange where
  typeGType :: ConstrainDoubleRange -> JSM GType
typeGType ConstrainDoubleRange
_ = JSM GType
gTypeConstrainDoubleRange
  {-# INLINE typeGType #-}

noConstrainDoubleRange :: Maybe ConstrainDoubleRange
noConstrainDoubleRange :: Maybe ConstrainDoubleRange
noConstrainDoubleRange = Maybe ConstrainDoubleRange
forall a. Maybe a
Nothing
{-# INLINE noConstrainDoubleRange #-}

gTypeConstrainDoubleRange :: JSM GType
gTypeConstrainDoubleRange :: JSM GType
gTypeConstrainDoubleRange = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ConstrainDoubleRange"

-- | Functions for this inteface are in "JSDOM.ConstrainLongRange".
-- Base interface functions are in:
--
--     * "JSDOM.LongRange"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ConstrainLongRange Mozilla ConstrainLongRange documentation>
newtype ConstrainLongRange = ConstrainLongRange { ConstrainLongRange -> JSVal
unConstrainLongRange :: JSVal }

instance PToJSVal ConstrainLongRange where
  pToJSVal :: ConstrainLongRange -> JSVal
pToJSVal = ConstrainLongRange -> JSVal
unConstrainLongRange
  {-# INLINE pToJSVal #-}

instance PFromJSVal ConstrainLongRange where
  pFromJSVal :: JSVal -> ConstrainLongRange
pFromJSVal = JSVal -> ConstrainLongRange
ConstrainLongRange
  {-# INLINE pFromJSVal #-}

instance ToJSVal ConstrainLongRange where
  toJSVal :: ConstrainLongRange -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ConstrainLongRange -> JSVal) -> ConstrainLongRange -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstrainLongRange -> JSVal
unConstrainLongRange
  {-# INLINE toJSVal #-}

instance FromJSVal ConstrainLongRange where
  fromJSVal :: JSVal -> JSM (Maybe ConstrainLongRange)
fromJSVal JSVal
v = (JSVal -> ConstrainLongRange)
-> Maybe JSVal -> Maybe ConstrainLongRange
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ConstrainLongRange
ConstrainLongRange (Maybe JSVal -> Maybe ConstrainLongRange)
-> JSM (Maybe JSVal) -> JSM (Maybe ConstrainLongRange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ConstrainLongRange
fromJSValUnchecked = ConstrainLongRange -> JSM ConstrainLongRange
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ConstrainLongRange -> JSM ConstrainLongRange)
-> (JSVal -> ConstrainLongRange) -> JSVal -> JSM ConstrainLongRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ConstrainLongRange
ConstrainLongRange
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ConstrainLongRange where
  makeObject :: ConstrainLongRange -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ConstrainLongRange -> JSVal)
-> ConstrainLongRange
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstrainLongRange -> JSVal
unConstrainLongRange

instance IsLongRange ConstrainLongRange
instance IsGObject ConstrainLongRange where
  typeGType :: ConstrainLongRange -> JSM GType
typeGType ConstrainLongRange
_ = JSM GType
gTypeConstrainLongRange
  {-# INLINE typeGType #-}

noConstrainLongRange :: Maybe ConstrainLongRange
noConstrainLongRange :: Maybe ConstrainLongRange
noConstrainLongRange = Maybe ConstrainLongRange
forall a. Maybe a
Nothing
{-# INLINE noConstrainLongRange #-}

gTypeConstrainLongRange :: JSM GType
gTypeConstrainLongRange :: JSM GType
gTypeConstrainLongRange = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ConstrainLongRange"

-- | Functions for this inteface are in "JSDOM.ConvolverNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ConvolverNode Mozilla ConvolverNode documentation>
newtype ConvolverNode = ConvolverNode { ConvolverNode -> JSVal
unConvolverNode :: JSVal }

instance PToJSVal ConvolverNode where
  pToJSVal :: ConvolverNode -> JSVal
pToJSVal = ConvolverNode -> JSVal
unConvolverNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal ConvolverNode where
  pFromJSVal :: JSVal -> ConvolverNode
pFromJSVal = JSVal -> ConvolverNode
ConvolverNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal ConvolverNode where
  toJSVal :: ConvolverNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ConvolverNode -> JSVal) -> ConvolverNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConvolverNode -> JSVal
unConvolverNode
  {-# INLINE toJSVal #-}

instance FromJSVal ConvolverNode where
  fromJSVal :: JSVal -> JSM (Maybe ConvolverNode)
fromJSVal JSVal
v = (JSVal -> ConvolverNode) -> Maybe JSVal -> Maybe ConvolverNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ConvolverNode
ConvolverNode (Maybe JSVal -> Maybe ConvolverNode)
-> JSM (Maybe JSVal) -> JSM (Maybe ConvolverNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ConvolverNode
fromJSValUnchecked = ConvolverNode -> JSM ConvolverNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ConvolverNode -> JSM ConvolverNode)
-> (JSVal -> ConvolverNode) -> JSVal -> JSM ConvolverNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ConvolverNode
ConvolverNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ConvolverNode where
  makeObject :: ConvolverNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ConvolverNode -> JSVal) -> ConvolverNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConvolverNode -> JSVal
unConvolverNode

instance IsAudioNode ConvolverNode
instance IsEventTarget ConvolverNode
instance IsGObject ConvolverNode where
  typeGType :: ConvolverNode -> JSM GType
typeGType ConvolverNode
_ = JSM GType
gTypeConvolverNode
  {-# INLINE typeGType #-}

noConvolverNode :: Maybe ConvolverNode
noConvolverNode :: Maybe ConvolverNode
noConvolverNode = Maybe ConvolverNode
forall a. Maybe a
Nothing
{-# INLINE noConvolverNode #-}

gTypeConvolverNode :: JSM GType
gTypeConvolverNode :: JSM GType
gTypeConvolverNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ConvolverNode"

-- | Functions for this inteface are in "JSDOM.Coordinates".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Coordinates Mozilla Coordinates documentation>
newtype Coordinates = Coordinates { Coordinates -> JSVal
unCoordinates :: JSVal }

instance PToJSVal Coordinates where
  pToJSVal :: Coordinates -> JSVal
pToJSVal = Coordinates -> JSVal
unCoordinates
  {-# INLINE pToJSVal #-}

instance PFromJSVal Coordinates where
  pFromJSVal :: JSVal -> Coordinates
pFromJSVal = JSVal -> Coordinates
Coordinates
  {-# INLINE pFromJSVal #-}

instance ToJSVal Coordinates where
  toJSVal :: Coordinates -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Coordinates -> JSVal) -> Coordinates -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates -> JSVal
unCoordinates
  {-# INLINE toJSVal #-}

instance FromJSVal Coordinates where
  fromJSVal :: JSVal -> JSM (Maybe Coordinates)
fromJSVal JSVal
v = (JSVal -> Coordinates) -> Maybe JSVal -> Maybe Coordinates
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Coordinates
Coordinates (Maybe JSVal -> Maybe Coordinates)
-> JSM (Maybe JSVal) -> JSM (Maybe Coordinates)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Coordinates
fromJSValUnchecked = Coordinates -> JSM Coordinates
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Coordinates -> JSM Coordinates)
-> (JSVal -> Coordinates) -> JSVal -> JSM Coordinates
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Coordinates
Coordinates
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Coordinates where
  makeObject :: Coordinates -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Coordinates -> JSVal) -> Coordinates -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coordinates -> JSVal
unCoordinates

instance IsGObject Coordinates where
  typeGType :: Coordinates -> JSM GType
typeGType Coordinates
_ = JSM GType
gTypeCoordinates
  {-# INLINE typeGType #-}

noCoordinates :: Maybe Coordinates
noCoordinates :: Maybe Coordinates
noCoordinates = Maybe Coordinates
forall a. Maybe a
Nothing
{-# INLINE noCoordinates #-}

gTypeCoordinates :: JSM GType
gTypeCoordinates :: JSM GType
gTypeCoordinates = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Coordinates"

-- | Functions for this inteface are in "JSDOM.CountQueuingStrategy".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CountQueuingStrategy Mozilla CountQueuingStrategy documentation>
newtype CountQueuingStrategy = CountQueuingStrategy { CountQueuingStrategy -> JSVal
unCountQueuingStrategy :: JSVal }

instance PToJSVal CountQueuingStrategy where
  pToJSVal :: CountQueuingStrategy -> JSVal
pToJSVal = CountQueuingStrategy -> JSVal
unCountQueuingStrategy
  {-# INLINE pToJSVal #-}

instance PFromJSVal CountQueuingStrategy where
  pFromJSVal :: JSVal -> CountQueuingStrategy
pFromJSVal = JSVal -> CountQueuingStrategy
CountQueuingStrategy
  {-# INLINE pFromJSVal #-}

instance ToJSVal CountQueuingStrategy where
  toJSVal :: CountQueuingStrategy -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CountQueuingStrategy -> JSVal)
-> CountQueuingStrategy
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CountQueuingStrategy -> JSVal
unCountQueuingStrategy
  {-# INLINE toJSVal #-}

instance FromJSVal CountQueuingStrategy where
  fromJSVal :: JSVal -> JSM (Maybe CountQueuingStrategy)
fromJSVal JSVal
v = (JSVal -> CountQueuingStrategy)
-> Maybe JSVal -> Maybe CountQueuingStrategy
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CountQueuingStrategy
CountQueuingStrategy (Maybe JSVal -> Maybe CountQueuingStrategy)
-> JSM (Maybe JSVal) -> JSM (Maybe CountQueuingStrategy)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CountQueuingStrategy
fromJSValUnchecked = CountQueuingStrategy -> JSM CountQueuingStrategy
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CountQueuingStrategy -> JSM CountQueuingStrategy)
-> (JSVal -> CountQueuingStrategy)
-> JSVal
-> JSM CountQueuingStrategy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CountQueuingStrategy
CountQueuingStrategy
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CountQueuingStrategy where
  makeObject :: CountQueuingStrategy -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CountQueuingStrategy -> JSVal)
-> CountQueuingStrategy
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CountQueuingStrategy -> JSVal
unCountQueuingStrategy

instance IsGObject CountQueuingStrategy where
  typeGType :: CountQueuingStrategy -> JSM GType
typeGType CountQueuingStrategy
_ = JSM GType
gTypeCountQueuingStrategy
  {-# INLINE typeGType #-}

noCountQueuingStrategy :: Maybe CountQueuingStrategy
noCountQueuingStrategy :: Maybe CountQueuingStrategy
noCountQueuingStrategy = Maybe CountQueuingStrategy
forall a. Maybe a
Nothing
{-# INLINE noCountQueuingStrategy #-}

gTypeCountQueuingStrategy :: JSM GType
gTypeCountQueuingStrategy :: JSM GType
gTypeCountQueuingStrategy = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CountQueuingStrategy"

-- | Functions for this inteface are in "JSDOM.Counter".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Counter Mozilla Counter documentation>
newtype Counter = Counter { Counter -> JSVal
unCounter :: JSVal }

instance PToJSVal Counter where
  pToJSVal :: Counter -> JSVal
pToJSVal = Counter -> JSVal
unCounter
  {-# INLINE pToJSVal #-}

instance PFromJSVal Counter where
  pFromJSVal :: JSVal -> Counter
pFromJSVal = JSVal -> Counter
Counter
  {-# INLINE pFromJSVal #-}

instance ToJSVal Counter where
  toJSVal :: Counter -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Counter -> JSVal) -> Counter -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Counter -> JSVal
unCounter
  {-# INLINE toJSVal #-}

instance FromJSVal Counter where
  fromJSVal :: JSVal -> JSM (Maybe Counter)
fromJSVal JSVal
v = (JSVal -> Counter) -> Maybe JSVal -> Maybe Counter
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Counter
Counter (Maybe JSVal -> Maybe Counter)
-> JSM (Maybe JSVal) -> JSM (Maybe Counter)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Counter
fromJSValUnchecked = Counter -> JSM Counter
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Counter -> JSM Counter)
-> (JSVal -> Counter) -> JSVal -> JSM Counter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Counter
Counter
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Counter where
  makeObject :: Counter -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Counter -> JSVal) -> Counter -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Counter -> JSVal
unCounter

instance IsGObject Counter where
  typeGType :: Counter -> JSM GType
typeGType Counter
_ = JSM GType
gTypeCounter
  {-# INLINE typeGType #-}

noCounter :: Maybe Counter
noCounter :: Maybe Counter
noCounter = Maybe Counter
forall a. Maybe a
Nothing
{-# INLINE noCounter #-}

gTypeCounter :: JSM GType
gTypeCounter :: JSM GType
gTypeCounter = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Counter"

-- | Functions for this inteface are in "JSDOM.CredentialData".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CredentialData Mozilla CredentialData documentation>
newtype CredentialData = CredentialData { CredentialData -> JSVal
unCredentialData :: JSVal }

instance PToJSVal CredentialData where
  pToJSVal :: CredentialData -> JSVal
pToJSVal = CredentialData -> JSVal
unCredentialData
  {-# INLINE pToJSVal #-}

instance PFromJSVal CredentialData where
  pFromJSVal :: JSVal -> CredentialData
pFromJSVal = JSVal -> CredentialData
CredentialData
  {-# INLINE pFromJSVal #-}

instance ToJSVal CredentialData where
  toJSVal :: CredentialData -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CredentialData -> JSVal) -> CredentialData -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CredentialData -> JSVal
unCredentialData
  {-# INLINE toJSVal #-}

instance FromJSVal CredentialData where
  fromJSVal :: JSVal -> JSM (Maybe CredentialData)
fromJSVal JSVal
v = (JSVal -> CredentialData) -> Maybe JSVal -> Maybe CredentialData
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CredentialData
CredentialData (Maybe JSVal -> Maybe CredentialData)
-> JSM (Maybe JSVal) -> JSM (Maybe CredentialData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CredentialData
fromJSValUnchecked = CredentialData -> JSM CredentialData
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CredentialData -> JSM CredentialData)
-> (JSVal -> CredentialData) -> JSVal -> JSM CredentialData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CredentialData
CredentialData
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CredentialData where
  makeObject :: CredentialData -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CredentialData -> JSVal) -> CredentialData -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CredentialData -> JSVal
unCredentialData

class (IsGObject o) => IsCredentialData o
toCredentialData :: IsCredentialData o => o -> CredentialData
toCredentialData :: forall o. IsCredentialData o => o -> CredentialData
toCredentialData = JSVal -> CredentialData
CredentialData (JSVal -> CredentialData) -> (o -> JSVal) -> o -> CredentialData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsCredentialData CredentialData
instance IsGObject CredentialData where
  typeGType :: CredentialData -> JSM GType
typeGType CredentialData
_ = JSM GType
gTypeCredentialData
  {-# INLINE typeGType #-}

noCredentialData :: Maybe CredentialData
noCredentialData :: Maybe CredentialData
noCredentialData = Maybe CredentialData
forall a. Maybe a
Nothing
{-# INLINE noCredentialData #-}

gTypeCredentialData :: JSM GType
gTypeCredentialData :: JSM GType
gTypeCredentialData = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CredentialData"

-- | Functions for this inteface are in "JSDOM.Crypto".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Crypto Mozilla Crypto documentation>
newtype Crypto = Crypto { Crypto -> JSVal
unCrypto :: JSVal }

instance PToJSVal Crypto where
  pToJSVal :: Crypto -> JSVal
pToJSVal = Crypto -> JSVal
unCrypto
  {-# INLINE pToJSVal #-}

instance PFromJSVal Crypto where
  pFromJSVal :: JSVal -> Crypto
pFromJSVal = JSVal -> Crypto
Crypto
  {-# INLINE pFromJSVal #-}

instance ToJSVal Crypto where
  toJSVal :: Crypto -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Crypto -> JSVal) -> Crypto -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Crypto -> JSVal
unCrypto
  {-# INLINE toJSVal #-}

instance FromJSVal Crypto where
  fromJSVal :: JSVal -> JSM (Maybe Crypto)
fromJSVal JSVal
v = (JSVal -> Crypto) -> Maybe JSVal -> Maybe Crypto
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Crypto
Crypto (Maybe JSVal -> Maybe Crypto)
-> JSM (Maybe JSVal) -> JSM (Maybe Crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Crypto
fromJSValUnchecked = Crypto -> JSM Crypto
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Crypto -> JSM Crypto) -> (JSVal -> Crypto) -> JSVal -> JSM Crypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Crypto
Crypto
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Crypto where
  makeObject :: Crypto -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Crypto -> JSVal) -> Crypto -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Crypto -> JSVal
unCrypto

instance IsGObject Crypto where
  typeGType :: Crypto -> JSM GType
typeGType Crypto
_ = JSM GType
gTypeCrypto
  {-# INLINE typeGType #-}

noCrypto :: Maybe Crypto
noCrypto :: Maybe Crypto
noCrypto = Maybe Crypto
forall a. Maybe a
Nothing
{-# INLINE noCrypto #-}

gTypeCrypto :: JSM GType
gTypeCrypto :: JSM GType
gTypeCrypto = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Crypto"

-- | Functions for this inteface are in "JSDOM.CryptoAlgorithmParameters".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CryptoAlgorithmParameters Mozilla CryptoAlgorithmParameters documentation>
newtype CryptoAlgorithmParameters = CryptoAlgorithmParameters { CryptoAlgorithmParameters -> JSVal
unCryptoAlgorithmParameters :: JSVal }

instance PToJSVal CryptoAlgorithmParameters where
  pToJSVal :: CryptoAlgorithmParameters -> JSVal
pToJSVal = CryptoAlgorithmParameters -> JSVal
unCryptoAlgorithmParameters
  {-# INLINE pToJSVal #-}

instance PFromJSVal CryptoAlgorithmParameters where
  pFromJSVal :: JSVal -> CryptoAlgorithmParameters
pFromJSVal = JSVal -> CryptoAlgorithmParameters
CryptoAlgorithmParameters
  {-# INLINE pFromJSVal #-}

instance ToJSVal CryptoAlgorithmParameters where
  toJSVal :: CryptoAlgorithmParameters -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CryptoAlgorithmParameters -> JSVal)
-> CryptoAlgorithmParameters
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CryptoAlgorithmParameters -> JSVal
unCryptoAlgorithmParameters
  {-# INLINE toJSVal #-}

instance FromJSVal CryptoAlgorithmParameters where
  fromJSVal :: JSVal -> JSM (Maybe CryptoAlgorithmParameters)
fromJSVal JSVal
v = (JSVal -> CryptoAlgorithmParameters)
-> Maybe JSVal -> Maybe CryptoAlgorithmParameters
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CryptoAlgorithmParameters
CryptoAlgorithmParameters (Maybe JSVal -> Maybe CryptoAlgorithmParameters)
-> JSM (Maybe JSVal) -> JSM (Maybe CryptoAlgorithmParameters)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CryptoAlgorithmParameters
fromJSValUnchecked = CryptoAlgorithmParameters -> JSM CryptoAlgorithmParameters
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CryptoAlgorithmParameters -> JSM CryptoAlgorithmParameters)
-> (JSVal -> CryptoAlgorithmParameters)
-> JSVal
-> JSM CryptoAlgorithmParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CryptoAlgorithmParameters
CryptoAlgorithmParameters
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CryptoAlgorithmParameters where
  makeObject :: CryptoAlgorithmParameters -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CryptoAlgorithmParameters -> JSVal)
-> CryptoAlgorithmParameters
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CryptoAlgorithmParameters -> JSVal
unCryptoAlgorithmParameters

class (IsGObject o) => IsCryptoAlgorithmParameters o
toCryptoAlgorithmParameters :: IsCryptoAlgorithmParameters o => o -> CryptoAlgorithmParameters
toCryptoAlgorithmParameters :: forall o.
IsCryptoAlgorithmParameters o =>
o -> CryptoAlgorithmParameters
toCryptoAlgorithmParameters = JSVal -> CryptoAlgorithmParameters
CryptoAlgorithmParameters (JSVal -> CryptoAlgorithmParameters)
-> (o -> JSVal) -> o -> CryptoAlgorithmParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsCryptoAlgorithmParameters CryptoAlgorithmParameters
instance IsGObject CryptoAlgorithmParameters where
  typeGType :: CryptoAlgorithmParameters -> JSM GType
typeGType CryptoAlgorithmParameters
_ = JSM GType
gTypeCryptoAlgorithmParameters
  {-# INLINE typeGType #-}

noCryptoAlgorithmParameters :: Maybe CryptoAlgorithmParameters
noCryptoAlgorithmParameters :: Maybe CryptoAlgorithmParameters
noCryptoAlgorithmParameters = Maybe CryptoAlgorithmParameters
forall a. Maybe a
Nothing
{-# INLINE noCryptoAlgorithmParameters #-}

gTypeCryptoAlgorithmParameters :: JSM GType
gTypeCryptoAlgorithmParameters :: JSM GType
gTypeCryptoAlgorithmParameters = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CryptoAlgorithmParameters"

-- | Functions for this inteface are in "JSDOM.CryptoKey".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CryptoKey Mozilla CryptoKey documentation>
newtype CryptoKey = CryptoKey { CryptoKey -> JSVal
unCryptoKey :: JSVal }

instance PToJSVal CryptoKey where
  pToJSVal :: CryptoKey -> JSVal
pToJSVal = CryptoKey -> JSVal
unCryptoKey
  {-# INLINE pToJSVal #-}

instance PFromJSVal CryptoKey where
  pFromJSVal :: JSVal -> CryptoKey
pFromJSVal = JSVal -> CryptoKey
CryptoKey
  {-# INLINE pFromJSVal #-}

instance ToJSVal CryptoKey where
  toJSVal :: CryptoKey -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CryptoKey -> JSVal) -> CryptoKey -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CryptoKey -> JSVal
unCryptoKey
  {-# INLINE toJSVal #-}

instance FromJSVal CryptoKey where
  fromJSVal :: JSVal -> JSM (Maybe CryptoKey)
fromJSVal JSVal
v = (JSVal -> CryptoKey) -> Maybe JSVal -> Maybe CryptoKey
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CryptoKey
CryptoKey (Maybe JSVal -> Maybe CryptoKey)
-> JSM (Maybe JSVal) -> JSM (Maybe CryptoKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CryptoKey
fromJSValUnchecked = CryptoKey -> JSM CryptoKey
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CryptoKey -> JSM CryptoKey)
-> (JSVal -> CryptoKey) -> JSVal -> JSM CryptoKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CryptoKey
CryptoKey
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CryptoKey where
  makeObject :: CryptoKey -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CryptoKey -> JSVal) -> CryptoKey -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CryptoKey -> JSVal
unCryptoKey

instance IsGObject CryptoKey where
  typeGType :: CryptoKey -> JSM GType
typeGType CryptoKey
_ = JSM GType
gTypeCryptoKey
  {-# INLINE typeGType #-}

noCryptoKey :: Maybe CryptoKey
noCryptoKey :: Maybe CryptoKey
noCryptoKey = Maybe CryptoKey
forall a. Maybe a
Nothing
{-# INLINE noCryptoKey #-}

gTypeCryptoKey :: JSM GType
gTypeCryptoKey :: JSM GType
gTypeCryptoKey = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CryptoKey"

-- | Functions for this inteface are in "JSDOM.CryptoKeyPair".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CryptoKeyPair Mozilla CryptoKeyPair documentation>
newtype CryptoKeyPair = CryptoKeyPair { CryptoKeyPair -> JSVal
unCryptoKeyPair :: JSVal }

instance PToJSVal CryptoKeyPair where
  pToJSVal :: CryptoKeyPair -> JSVal
pToJSVal = CryptoKeyPair -> JSVal
unCryptoKeyPair
  {-# INLINE pToJSVal #-}

instance PFromJSVal CryptoKeyPair where
  pFromJSVal :: JSVal -> CryptoKeyPair
pFromJSVal = JSVal -> CryptoKeyPair
CryptoKeyPair
  {-# INLINE pFromJSVal #-}

instance ToJSVal CryptoKeyPair where
  toJSVal :: CryptoKeyPair -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CryptoKeyPair -> JSVal) -> CryptoKeyPair -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CryptoKeyPair -> JSVal
unCryptoKeyPair
  {-# INLINE toJSVal #-}

instance FromJSVal CryptoKeyPair where
  fromJSVal :: JSVal -> JSM (Maybe CryptoKeyPair)
fromJSVal JSVal
v = (JSVal -> CryptoKeyPair) -> Maybe JSVal -> Maybe CryptoKeyPair
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CryptoKeyPair
CryptoKeyPair (Maybe JSVal -> Maybe CryptoKeyPair)
-> JSM (Maybe JSVal) -> JSM (Maybe CryptoKeyPair)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CryptoKeyPair
fromJSValUnchecked = CryptoKeyPair -> JSM CryptoKeyPair
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CryptoKeyPair -> JSM CryptoKeyPair)
-> (JSVal -> CryptoKeyPair) -> JSVal -> JSM CryptoKeyPair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CryptoKeyPair
CryptoKeyPair
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CryptoKeyPair where
  makeObject :: CryptoKeyPair -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CryptoKeyPair -> JSVal) -> CryptoKeyPair -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CryptoKeyPair -> JSVal
unCryptoKeyPair

instance IsGObject CryptoKeyPair where
  typeGType :: CryptoKeyPair -> JSM GType
typeGType CryptoKeyPair
_ = JSM GType
gTypeCryptoKeyPair
  {-# INLINE typeGType #-}

noCryptoKeyPair :: Maybe CryptoKeyPair
noCryptoKeyPair :: Maybe CryptoKeyPair
noCryptoKeyPair = Maybe CryptoKeyPair
forall a. Maybe a
Nothing
{-# INLINE noCryptoKeyPair #-}

gTypeCryptoKeyPair :: JSM GType
gTypeCryptoKeyPair :: JSM GType
gTypeCryptoKeyPair = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CryptoKeyPair"

-- | Functions for this inteface are in "JSDOM.CustomElementRegistry".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CustomElementRegistry Mozilla CustomElementRegistry documentation>
newtype CustomElementRegistry = CustomElementRegistry { CustomElementRegistry -> JSVal
unCustomElementRegistry :: JSVal }

instance PToJSVal CustomElementRegistry where
  pToJSVal :: CustomElementRegistry -> JSVal
pToJSVal = CustomElementRegistry -> JSVal
unCustomElementRegistry
  {-# INLINE pToJSVal #-}

instance PFromJSVal CustomElementRegistry where
  pFromJSVal :: JSVal -> CustomElementRegistry
pFromJSVal = JSVal -> CustomElementRegistry
CustomElementRegistry
  {-# INLINE pFromJSVal #-}

instance ToJSVal CustomElementRegistry where
  toJSVal :: CustomElementRegistry -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CustomElementRegistry -> JSVal)
-> CustomElementRegistry
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CustomElementRegistry -> JSVal
unCustomElementRegistry
  {-# INLINE toJSVal #-}

instance FromJSVal CustomElementRegistry where
  fromJSVal :: JSVal -> JSM (Maybe CustomElementRegistry)
fromJSVal JSVal
v = (JSVal -> CustomElementRegistry)
-> Maybe JSVal -> Maybe CustomElementRegistry
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CustomElementRegistry
CustomElementRegistry (Maybe JSVal -> Maybe CustomElementRegistry)
-> JSM (Maybe JSVal) -> JSM (Maybe CustomElementRegistry)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CustomElementRegistry
fromJSValUnchecked = CustomElementRegistry -> JSM CustomElementRegistry
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CustomElementRegistry -> JSM CustomElementRegistry)
-> (JSVal -> CustomElementRegistry)
-> JSVal
-> JSM CustomElementRegistry
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CustomElementRegistry
CustomElementRegistry
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CustomElementRegistry where
  makeObject :: CustomElementRegistry -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CustomElementRegistry -> JSVal)
-> CustomElementRegistry
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CustomElementRegistry -> JSVal
unCustomElementRegistry

instance IsGObject CustomElementRegistry where
  typeGType :: CustomElementRegistry -> JSM GType
typeGType CustomElementRegistry
_ = JSM GType
gTypeCustomElementRegistry
  {-# INLINE typeGType #-}

noCustomElementRegistry :: Maybe CustomElementRegistry
noCustomElementRegistry :: Maybe CustomElementRegistry
noCustomElementRegistry = Maybe CustomElementRegistry
forall a. Maybe a
Nothing
{-# INLINE noCustomElementRegistry #-}

gTypeCustomElementRegistry :: JSM GType
gTypeCustomElementRegistry :: JSM GType
gTypeCustomElementRegistry = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CustomElementRegistry"

-- | Functions for this inteface are in "JSDOM.CustomEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CustomEvent Mozilla CustomEvent documentation>
newtype CustomEvent = CustomEvent { CustomEvent -> JSVal
unCustomEvent :: JSVal }

instance PToJSVal CustomEvent where
  pToJSVal :: CustomEvent -> JSVal
pToJSVal = CustomEvent -> JSVal
unCustomEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal CustomEvent where
  pFromJSVal :: JSVal -> CustomEvent
pFromJSVal = JSVal -> CustomEvent
CustomEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal CustomEvent where
  toJSVal :: CustomEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CustomEvent -> JSVal) -> CustomEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CustomEvent -> JSVal
unCustomEvent
  {-# INLINE toJSVal #-}

instance FromJSVal CustomEvent where
  fromJSVal :: JSVal -> JSM (Maybe CustomEvent)
fromJSVal JSVal
v = (JSVal -> CustomEvent) -> Maybe JSVal -> Maybe CustomEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CustomEvent
CustomEvent (Maybe JSVal -> Maybe CustomEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe CustomEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CustomEvent
fromJSValUnchecked = CustomEvent -> JSM CustomEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CustomEvent -> JSM CustomEvent)
-> (JSVal -> CustomEvent) -> JSVal -> JSM CustomEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CustomEvent
CustomEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CustomEvent where
  makeObject :: CustomEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CustomEvent -> JSVal) -> CustomEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CustomEvent -> JSVal
unCustomEvent

instance IsEvent CustomEvent
instance IsGObject CustomEvent where
  typeGType :: CustomEvent -> JSM GType
typeGType CustomEvent
_ = JSM GType
gTypeCustomEvent
  {-# INLINE typeGType #-}

noCustomEvent :: Maybe CustomEvent
noCustomEvent :: Maybe CustomEvent
noCustomEvent = Maybe CustomEvent
forall a. Maybe a
Nothing
{-# INLINE noCustomEvent #-}

gTypeCustomEvent :: JSM GType
gTypeCustomEvent :: JSM GType
gTypeCustomEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CustomEvent"

-- | Functions for this inteface are in "JSDOM.CustomEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/CustomEventInit Mozilla CustomEventInit documentation>
newtype CustomEventInit = CustomEventInit { CustomEventInit -> JSVal
unCustomEventInit :: JSVal }

instance PToJSVal CustomEventInit where
  pToJSVal :: CustomEventInit -> JSVal
pToJSVal = CustomEventInit -> JSVal
unCustomEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal CustomEventInit where
  pFromJSVal :: JSVal -> CustomEventInit
pFromJSVal = JSVal -> CustomEventInit
CustomEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal CustomEventInit where
  toJSVal :: CustomEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (CustomEventInit -> JSVal) -> CustomEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CustomEventInit -> JSVal
unCustomEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal CustomEventInit where
  fromJSVal :: JSVal -> JSM (Maybe CustomEventInit)
fromJSVal JSVal
v = (JSVal -> CustomEventInit) -> Maybe JSVal -> Maybe CustomEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> CustomEventInit
CustomEventInit (Maybe JSVal -> Maybe CustomEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe CustomEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM CustomEventInit
fromJSValUnchecked = CustomEventInit -> JSM CustomEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (CustomEventInit -> JSM CustomEventInit)
-> (JSVal -> CustomEventInit) -> JSVal -> JSM CustomEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> CustomEventInit
CustomEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject CustomEventInit where
  makeObject :: CustomEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (CustomEventInit -> JSVal) -> CustomEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CustomEventInit -> JSVal
unCustomEventInit

instance IsEventInit CustomEventInit
instance IsGObject CustomEventInit where
  typeGType :: CustomEventInit -> JSM GType
typeGType CustomEventInit
_ = JSM GType
gTypeCustomEventInit
  {-# INLINE typeGType #-}

noCustomEventInit :: Maybe CustomEventInit
noCustomEventInit :: Maybe CustomEventInit
noCustomEventInit = Maybe CustomEventInit
forall a. Maybe a
Nothing
{-# INLINE noCustomEventInit #-}

gTypeCustomEventInit :: JSM GType
gTypeCustomEventInit :: JSM GType
gTypeCustomEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"CustomEventInit"

-- | Functions for this inteface are in "JSDOM.DOMError".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMError Mozilla DOMError documentation>
newtype DOMError = DOMError { DOMError -> JSVal
unDOMError :: JSVal }

instance PToJSVal DOMError where
  pToJSVal :: DOMError -> JSVal
pToJSVal = DOMError -> JSVal
unDOMError
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMError where
  pFromJSVal :: JSVal -> DOMError
pFromJSVal = JSVal -> DOMError
DOMError
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMError where
  toJSVal :: DOMError -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMError -> JSVal) -> DOMError -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMError -> JSVal
unDOMError
  {-# INLINE toJSVal #-}

instance FromJSVal DOMError where
  fromJSVal :: JSVal -> JSM (Maybe DOMError)
fromJSVal JSVal
v = (JSVal -> DOMError) -> Maybe JSVal -> Maybe DOMError
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMError
DOMError (Maybe JSVal -> Maybe DOMError)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMError
fromJSValUnchecked = DOMError -> JSM DOMError
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMError -> JSM DOMError)
-> (JSVal -> DOMError) -> JSVal -> JSM DOMError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMError
DOMError
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMError where
  makeObject :: DOMError -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMError -> JSVal) -> DOMError -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMError -> JSVal
unDOMError

class (IsGObject o) => IsDOMError o
toDOMError :: IsDOMError o => o -> DOMError
toDOMError :: forall o. IsDOMError o => o -> DOMError
toDOMError = JSVal -> DOMError
DOMError (JSVal -> DOMError) -> (o -> JSVal) -> o -> DOMError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsDOMError DOMError
instance IsGObject DOMError where
  typeGType :: DOMError -> JSM GType
typeGType DOMError
_ = JSM GType
gTypeDOMError
  {-# INLINE typeGType #-}

noDOMError :: Maybe DOMError
noDOMError :: Maybe DOMError
noDOMError = Maybe DOMError
forall a. Maybe a
Nothing
{-# INLINE noDOMError #-}

gTypeDOMError :: JSM GType
gTypeDOMError :: JSM GType
gTypeDOMError = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMError"

-- | Functions for this inteface are in "JSDOM.DOMException".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMException Mozilla DOMException documentation>
newtype DOMException = DOMException { DOMException -> JSVal
unDOMException :: JSVal }

instance PToJSVal DOMException where
  pToJSVal :: DOMException -> JSVal
pToJSVal = DOMException -> JSVal
unDOMException
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMException where
  pFromJSVal :: JSVal -> DOMException
pFromJSVal = JSVal -> DOMException
DOMException
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMException where
  toJSVal :: DOMException -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMException -> JSVal) -> DOMException -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMException -> JSVal
unDOMException
  {-# INLINE toJSVal #-}

instance FromJSVal DOMException where
  fromJSVal :: JSVal -> JSM (Maybe DOMException)
fromJSVal JSVal
v = (JSVal -> DOMException) -> Maybe JSVal -> Maybe DOMException
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMException
DOMException (Maybe JSVal -> Maybe DOMException)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMException)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMException
fromJSValUnchecked = DOMException -> JSM DOMException
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMException -> JSM DOMException)
-> (JSVal -> DOMException) -> JSVal -> JSM DOMException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMException
DOMException
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMException where
  makeObject :: DOMException -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMException -> JSVal) -> DOMException -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMException -> JSVal
unDOMException

instance IsGObject DOMException where
  typeGType :: DOMException -> JSM GType
typeGType DOMException
_ = JSM GType
gTypeDOMException
  {-# INLINE typeGType #-}

noDOMException :: Maybe DOMException
noDOMException :: Maybe DOMException
noDOMException = Maybe DOMException
forall a. Maybe a
Nothing
{-# INLINE noDOMException #-}

gTypeDOMException :: JSM GType
gTypeDOMException :: JSM GType
gTypeDOMException = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMException"

-- | Functions for this inteface are in "JSDOM.DOMImplementation".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMImplementation Mozilla DOMImplementation documentation>
newtype DOMImplementation = DOMImplementation { DOMImplementation -> JSVal
unDOMImplementation :: JSVal }

instance PToJSVal DOMImplementation where
  pToJSVal :: DOMImplementation -> JSVal
pToJSVal = DOMImplementation -> JSVal
unDOMImplementation
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMImplementation where
  pFromJSVal :: JSVal -> DOMImplementation
pFromJSVal = JSVal -> DOMImplementation
DOMImplementation
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMImplementation where
  toJSVal :: DOMImplementation -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMImplementation -> JSVal) -> DOMImplementation -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMImplementation -> JSVal
unDOMImplementation
  {-# INLINE toJSVal #-}

instance FromJSVal DOMImplementation where
  fromJSVal :: JSVal -> JSM (Maybe DOMImplementation)
fromJSVal JSVal
v = (JSVal -> DOMImplementation)
-> Maybe JSVal -> Maybe DOMImplementation
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMImplementation
DOMImplementation (Maybe JSVal -> Maybe DOMImplementation)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMImplementation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMImplementation
fromJSValUnchecked = DOMImplementation -> JSM DOMImplementation
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMImplementation -> JSM DOMImplementation)
-> (JSVal -> DOMImplementation) -> JSVal -> JSM DOMImplementation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMImplementation
DOMImplementation
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMImplementation where
  makeObject :: DOMImplementation -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMImplementation -> JSVal) -> DOMImplementation -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMImplementation -> JSVal
unDOMImplementation

instance IsGObject DOMImplementation where
  typeGType :: DOMImplementation -> JSM GType
typeGType DOMImplementation
_ = JSM GType
gTypeDOMImplementation
  {-# INLINE typeGType #-}

noDOMImplementation :: Maybe DOMImplementation
noDOMImplementation :: Maybe DOMImplementation
noDOMImplementation = Maybe DOMImplementation
forall a. Maybe a
Nothing
{-# INLINE noDOMImplementation #-}

gTypeDOMImplementation :: JSM GType
gTypeDOMImplementation :: JSM GType
gTypeDOMImplementation = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMImplementation"

-- | Functions for this inteface are in "JSDOM.DOMNamedFlowCollection".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitNamedFlowCollection Mozilla WebKitNamedFlowCollection documentation>
newtype DOMNamedFlowCollection = DOMNamedFlowCollection { DOMNamedFlowCollection -> JSVal
unDOMNamedFlowCollection :: JSVal }

instance PToJSVal DOMNamedFlowCollection where
  pToJSVal :: DOMNamedFlowCollection -> JSVal
pToJSVal = DOMNamedFlowCollection -> JSVal
unDOMNamedFlowCollection
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMNamedFlowCollection where
  pFromJSVal :: JSVal -> DOMNamedFlowCollection
pFromJSVal = JSVal -> DOMNamedFlowCollection
DOMNamedFlowCollection
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMNamedFlowCollection where
  toJSVal :: DOMNamedFlowCollection -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMNamedFlowCollection -> JSVal)
-> DOMNamedFlowCollection
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMNamedFlowCollection -> JSVal
unDOMNamedFlowCollection
  {-# INLINE toJSVal #-}

instance FromJSVal DOMNamedFlowCollection where
  fromJSVal :: JSVal -> JSM (Maybe DOMNamedFlowCollection)
fromJSVal JSVal
v = (JSVal -> DOMNamedFlowCollection)
-> Maybe JSVal -> Maybe DOMNamedFlowCollection
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMNamedFlowCollection
DOMNamedFlowCollection (Maybe JSVal -> Maybe DOMNamedFlowCollection)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMNamedFlowCollection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMNamedFlowCollection
fromJSValUnchecked = DOMNamedFlowCollection -> JSM DOMNamedFlowCollection
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMNamedFlowCollection -> JSM DOMNamedFlowCollection)
-> (JSVal -> DOMNamedFlowCollection)
-> JSVal
-> JSM DOMNamedFlowCollection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMNamedFlowCollection
DOMNamedFlowCollection
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMNamedFlowCollection where
  makeObject :: DOMNamedFlowCollection -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMNamedFlowCollection -> JSVal)
-> DOMNamedFlowCollection
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMNamedFlowCollection -> JSVal
unDOMNamedFlowCollection

instance IsGObject DOMNamedFlowCollection where
  typeGType :: DOMNamedFlowCollection -> JSM GType
typeGType DOMNamedFlowCollection
_ = JSM GType
gTypeDOMNamedFlowCollection
  {-# INLINE typeGType #-}

noDOMNamedFlowCollection :: Maybe DOMNamedFlowCollection
noDOMNamedFlowCollection :: Maybe DOMNamedFlowCollection
noDOMNamedFlowCollection = Maybe DOMNamedFlowCollection
forall a. Maybe a
Nothing
{-# INLINE noDOMNamedFlowCollection #-}

gTypeDOMNamedFlowCollection :: JSM GType
gTypeDOMNamedFlowCollection :: JSM GType
gTypeDOMNamedFlowCollection = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitNamedFlowCollection"

-- | Functions for this inteface are in "JSDOM.DOMParser".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMParser Mozilla DOMParser documentation>
newtype DOMParser = DOMParser { DOMParser -> JSVal
unDOMParser :: JSVal }

instance PToJSVal DOMParser where
  pToJSVal :: DOMParser -> JSVal
pToJSVal = DOMParser -> JSVal
unDOMParser
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMParser where
  pFromJSVal :: JSVal -> DOMParser
pFromJSVal = JSVal -> DOMParser
DOMParser
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMParser where
  toJSVal :: DOMParser -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMParser -> JSVal) -> DOMParser -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMParser -> JSVal
unDOMParser
  {-# INLINE toJSVal #-}

instance FromJSVal DOMParser where
  fromJSVal :: JSVal -> JSM (Maybe DOMParser)
fromJSVal JSVal
v = (JSVal -> DOMParser) -> Maybe JSVal -> Maybe DOMParser
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMParser
DOMParser (Maybe JSVal -> Maybe DOMParser)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMParser)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMParser
fromJSValUnchecked = DOMParser -> JSM DOMParser
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMParser -> JSM DOMParser)
-> (JSVal -> DOMParser) -> JSVal -> JSM DOMParser
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMParser
DOMParser
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMParser where
  makeObject :: DOMParser -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMParser -> JSVal) -> DOMParser -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMParser -> JSVal
unDOMParser

instance IsGObject DOMParser where
  typeGType :: DOMParser -> JSM GType
typeGType DOMParser
_ = JSM GType
gTypeDOMParser
  {-# INLINE typeGType #-}

noDOMParser :: Maybe DOMParser
noDOMParser :: Maybe DOMParser
noDOMParser = Maybe DOMParser
forall a. Maybe a
Nothing
{-# INLINE noDOMParser #-}

gTypeDOMParser :: JSM GType
gTypeDOMParser :: JSM GType
gTypeDOMParser = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMParser"

-- | Functions for this inteface are in "JSDOM.DOMPoint".
-- Base interface functions are in:
--
--     * "JSDOM.DOMPointReadOnly"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMPoint Mozilla DOMPoint documentation>
newtype DOMPoint = DOMPoint { DOMPoint -> JSVal
unDOMPoint :: JSVal }

instance PToJSVal DOMPoint where
  pToJSVal :: DOMPoint -> JSVal
pToJSVal = DOMPoint -> JSVal
unDOMPoint
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMPoint where
  pFromJSVal :: JSVal -> DOMPoint
pFromJSVal = JSVal -> DOMPoint
DOMPoint
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMPoint where
  toJSVal :: DOMPoint -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMPoint -> JSVal) -> DOMPoint -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMPoint -> JSVal
unDOMPoint
  {-# INLINE toJSVal #-}

instance FromJSVal DOMPoint where
  fromJSVal :: JSVal -> JSM (Maybe DOMPoint)
fromJSVal JSVal
v = (JSVal -> DOMPoint) -> Maybe JSVal -> Maybe DOMPoint
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMPoint
DOMPoint (Maybe JSVal -> Maybe DOMPoint)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMPoint)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMPoint
fromJSValUnchecked = DOMPoint -> JSM DOMPoint
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMPoint -> JSM DOMPoint)
-> (JSVal -> DOMPoint) -> JSVal -> JSM DOMPoint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMPoint
DOMPoint
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMPoint where
  makeObject :: DOMPoint -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMPoint -> JSVal) -> DOMPoint -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMPoint -> JSVal
unDOMPoint

instance IsDOMPointReadOnly DOMPoint
instance IsGObject DOMPoint where
  typeGType :: DOMPoint -> JSM GType
typeGType DOMPoint
_ = JSM GType
gTypeDOMPoint
  {-# INLINE typeGType #-}

noDOMPoint :: Maybe DOMPoint
noDOMPoint :: Maybe DOMPoint
noDOMPoint = Maybe DOMPoint
forall a. Maybe a
Nothing
{-# INLINE noDOMPoint #-}

gTypeDOMPoint :: JSM GType
gTypeDOMPoint :: JSM GType
gTypeDOMPoint = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMPoint"

-- | Functions for this inteface are in "JSDOM.DOMPointInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMPointInit Mozilla DOMPointInit documentation>
newtype DOMPointInit = DOMPointInit { DOMPointInit -> JSVal
unDOMPointInit :: JSVal }

instance PToJSVal DOMPointInit where
  pToJSVal :: DOMPointInit -> JSVal
pToJSVal = DOMPointInit -> JSVal
unDOMPointInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMPointInit where
  pFromJSVal :: JSVal -> DOMPointInit
pFromJSVal = JSVal -> DOMPointInit
DOMPointInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMPointInit where
  toJSVal :: DOMPointInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMPointInit -> JSVal) -> DOMPointInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMPointInit -> JSVal
unDOMPointInit
  {-# INLINE toJSVal #-}

instance FromJSVal DOMPointInit where
  fromJSVal :: JSVal -> JSM (Maybe DOMPointInit)
fromJSVal JSVal
v = (JSVal -> DOMPointInit) -> Maybe JSVal -> Maybe DOMPointInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMPointInit
DOMPointInit (Maybe JSVal -> Maybe DOMPointInit)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMPointInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMPointInit
fromJSValUnchecked = DOMPointInit -> JSM DOMPointInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMPointInit -> JSM DOMPointInit)
-> (JSVal -> DOMPointInit) -> JSVal -> JSM DOMPointInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMPointInit
DOMPointInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMPointInit where
  makeObject :: DOMPointInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMPointInit -> JSVal) -> DOMPointInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMPointInit -> JSVal
unDOMPointInit

instance IsGObject DOMPointInit where
  typeGType :: DOMPointInit -> JSM GType
typeGType DOMPointInit
_ = JSM GType
gTypeDOMPointInit
  {-# INLINE typeGType #-}

noDOMPointInit :: Maybe DOMPointInit
noDOMPointInit :: Maybe DOMPointInit
noDOMPointInit = Maybe DOMPointInit
forall a. Maybe a
Nothing
{-# INLINE noDOMPointInit #-}

gTypeDOMPointInit :: JSM GType
gTypeDOMPointInit :: JSM GType
gTypeDOMPointInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMPointInit"

-- | Functions for this inteface are in "JSDOM.DOMPointReadOnly".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMPointReadOnly Mozilla DOMPointReadOnly documentation>
newtype DOMPointReadOnly = DOMPointReadOnly { DOMPointReadOnly -> JSVal
unDOMPointReadOnly :: JSVal }

instance PToJSVal DOMPointReadOnly where
  pToJSVal :: DOMPointReadOnly -> JSVal
pToJSVal = DOMPointReadOnly -> JSVal
unDOMPointReadOnly
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMPointReadOnly where
  pFromJSVal :: JSVal -> DOMPointReadOnly
pFromJSVal = JSVal -> DOMPointReadOnly
DOMPointReadOnly
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMPointReadOnly where
  toJSVal :: DOMPointReadOnly -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMPointReadOnly -> JSVal) -> DOMPointReadOnly -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMPointReadOnly -> JSVal
unDOMPointReadOnly
  {-# INLINE toJSVal #-}

instance FromJSVal DOMPointReadOnly where
  fromJSVal :: JSVal -> JSM (Maybe DOMPointReadOnly)
fromJSVal JSVal
v = (JSVal -> DOMPointReadOnly)
-> Maybe JSVal -> Maybe DOMPointReadOnly
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMPointReadOnly
DOMPointReadOnly (Maybe JSVal -> Maybe DOMPointReadOnly)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMPointReadOnly)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMPointReadOnly
fromJSValUnchecked = DOMPointReadOnly -> JSM DOMPointReadOnly
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMPointReadOnly -> JSM DOMPointReadOnly)
-> (JSVal -> DOMPointReadOnly) -> JSVal -> JSM DOMPointReadOnly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMPointReadOnly
DOMPointReadOnly
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMPointReadOnly where
  makeObject :: DOMPointReadOnly -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMPointReadOnly -> JSVal) -> DOMPointReadOnly -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMPointReadOnly -> JSVal
unDOMPointReadOnly

class (IsGObject o) => IsDOMPointReadOnly o
toDOMPointReadOnly :: IsDOMPointReadOnly o => o -> DOMPointReadOnly
toDOMPointReadOnly :: forall o. IsDOMPointReadOnly o => o -> DOMPointReadOnly
toDOMPointReadOnly = JSVal -> DOMPointReadOnly
DOMPointReadOnly (JSVal -> DOMPointReadOnly)
-> (o -> JSVal) -> o -> DOMPointReadOnly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsDOMPointReadOnly DOMPointReadOnly
instance IsGObject DOMPointReadOnly where
  typeGType :: DOMPointReadOnly -> JSM GType
typeGType DOMPointReadOnly
_ = JSM GType
gTypeDOMPointReadOnly
  {-# INLINE typeGType #-}

noDOMPointReadOnly :: Maybe DOMPointReadOnly
noDOMPointReadOnly :: Maybe DOMPointReadOnly
noDOMPointReadOnly = Maybe DOMPointReadOnly
forall a. Maybe a
Nothing
{-# INLINE noDOMPointReadOnly #-}

gTypeDOMPointReadOnly :: JSM GType
gTypeDOMPointReadOnly :: JSM GType
gTypeDOMPointReadOnly = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMPointReadOnly"

-- | Functions for this inteface are in "JSDOM.DOMRect".
-- Base interface functions are in:
--
--     * "JSDOM.DOMRectReadOnly"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMRect Mozilla DOMRect documentation>
newtype DOMRect = DOMRect { DOMRect -> JSVal
unDOMRect :: JSVal }

instance PToJSVal DOMRect where
  pToJSVal :: DOMRect -> JSVal
pToJSVal = DOMRect -> JSVal
unDOMRect
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMRect where
  pFromJSVal :: JSVal -> DOMRect
pFromJSVal = JSVal -> DOMRect
DOMRect
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMRect where
  toJSVal :: DOMRect -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (DOMRect -> JSVal) -> DOMRect -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMRect -> JSVal
unDOMRect
  {-# INLINE toJSVal #-}

instance FromJSVal DOMRect where
  fromJSVal :: JSVal -> JSM (Maybe DOMRect)
fromJSVal JSVal
v = (JSVal -> DOMRect) -> Maybe JSVal -> Maybe DOMRect
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMRect
DOMRect (Maybe JSVal -> Maybe DOMRect)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMRect)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMRect
fromJSValUnchecked = DOMRect -> JSM DOMRect
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMRect -> JSM DOMRect)
-> (JSVal -> DOMRect) -> JSVal -> JSM DOMRect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMRect
DOMRect
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMRect where
  makeObject :: DOMRect -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMRect -> JSVal) -> DOMRect -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMRect -> JSVal
unDOMRect

instance IsDOMRectReadOnly DOMRect
instance IsGObject DOMRect where
  typeGType :: DOMRect -> JSM GType
typeGType DOMRect
_ = JSM GType
gTypeDOMRect
  {-# INLINE typeGType #-}

noDOMRect :: Maybe DOMRect
noDOMRect :: Maybe DOMRect
noDOMRect = Maybe DOMRect
forall a. Maybe a
Nothing
{-# INLINE noDOMRect #-}

gTypeDOMRect :: JSM GType
gTypeDOMRect :: JSM GType
gTypeDOMRect = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMRect"

-- | Functions for this inteface are in "JSDOM.DOMRectInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMRectInit Mozilla DOMRectInit documentation>
newtype DOMRectInit = DOMRectInit { DOMRectInit -> JSVal
unDOMRectInit :: JSVal }

instance PToJSVal DOMRectInit where
  pToJSVal :: DOMRectInit -> JSVal
pToJSVal = DOMRectInit -> JSVal
unDOMRectInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMRectInit where
  pFromJSVal :: JSVal -> DOMRectInit
pFromJSVal = JSVal -> DOMRectInit
DOMRectInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMRectInit where
  toJSVal :: DOMRectInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMRectInit -> JSVal) -> DOMRectInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMRectInit -> JSVal
unDOMRectInit
  {-# INLINE toJSVal #-}

instance FromJSVal DOMRectInit where
  fromJSVal :: JSVal -> JSM (Maybe DOMRectInit)
fromJSVal JSVal
v = (JSVal -> DOMRectInit) -> Maybe JSVal -> Maybe DOMRectInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMRectInit
DOMRectInit (Maybe JSVal -> Maybe DOMRectInit)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMRectInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMRectInit
fromJSValUnchecked = DOMRectInit -> JSM DOMRectInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMRectInit -> JSM DOMRectInit)
-> (JSVal -> DOMRectInit) -> JSVal -> JSM DOMRectInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMRectInit
DOMRectInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMRectInit where
  makeObject :: DOMRectInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMRectInit -> JSVal) -> DOMRectInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMRectInit -> JSVal
unDOMRectInit

instance IsGObject DOMRectInit where
  typeGType :: DOMRectInit -> JSM GType
typeGType DOMRectInit
_ = JSM GType
gTypeDOMRectInit
  {-# INLINE typeGType #-}

noDOMRectInit :: Maybe DOMRectInit
noDOMRectInit :: Maybe DOMRectInit
noDOMRectInit = Maybe DOMRectInit
forall a. Maybe a
Nothing
{-# INLINE noDOMRectInit #-}

gTypeDOMRectInit :: JSM GType
gTypeDOMRectInit :: JSM GType
gTypeDOMRectInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMRectInit"

-- | Functions for this inteface are in "JSDOM.DOMRectReadOnly".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMRectReadOnly Mozilla DOMRectReadOnly documentation>
newtype DOMRectReadOnly = DOMRectReadOnly { DOMRectReadOnly -> JSVal
unDOMRectReadOnly :: JSVal }

instance PToJSVal DOMRectReadOnly where
  pToJSVal :: DOMRectReadOnly -> JSVal
pToJSVal = DOMRectReadOnly -> JSVal
unDOMRectReadOnly
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMRectReadOnly where
  pFromJSVal :: JSVal -> DOMRectReadOnly
pFromJSVal = JSVal -> DOMRectReadOnly
DOMRectReadOnly
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMRectReadOnly where
  toJSVal :: DOMRectReadOnly -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMRectReadOnly -> JSVal) -> DOMRectReadOnly -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMRectReadOnly -> JSVal
unDOMRectReadOnly
  {-# INLINE toJSVal #-}

instance FromJSVal DOMRectReadOnly where
  fromJSVal :: JSVal -> JSM (Maybe DOMRectReadOnly)
fromJSVal JSVal
v = (JSVal -> DOMRectReadOnly) -> Maybe JSVal -> Maybe DOMRectReadOnly
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMRectReadOnly
DOMRectReadOnly (Maybe JSVal -> Maybe DOMRectReadOnly)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMRectReadOnly)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMRectReadOnly
fromJSValUnchecked = DOMRectReadOnly -> JSM DOMRectReadOnly
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMRectReadOnly -> JSM DOMRectReadOnly)
-> (JSVal -> DOMRectReadOnly) -> JSVal -> JSM DOMRectReadOnly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMRectReadOnly
DOMRectReadOnly
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMRectReadOnly where
  makeObject :: DOMRectReadOnly -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMRectReadOnly -> JSVal) -> DOMRectReadOnly -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMRectReadOnly -> JSVal
unDOMRectReadOnly

class (IsGObject o) => IsDOMRectReadOnly o
toDOMRectReadOnly :: IsDOMRectReadOnly o => o -> DOMRectReadOnly
toDOMRectReadOnly :: forall o. IsDOMRectReadOnly o => o -> DOMRectReadOnly
toDOMRectReadOnly = JSVal -> DOMRectReadOnly
DOMRectReadOnly (JSVal -> DOMRectReadOnly) -> (o -> JSVal) -> o -> DOMRectReadOnly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsDOMRectReadOnly DOMRectReadOnly
instance IsGObject DOMRectReadOnly where
  typeGType :: DOMRectReadOnly -> JSM GType
typeGType DOMRectReadOnly
_ = JSM GType
gTypeDOMRectReadOnly
  {-# INLINE typeGType #-}

noDOMRectReadOnly :: Maybe DOMRectReadOnly
noDOMRectReadOnly :: Maybe DOMRectReadOnly
noDOMRectReadOnly = Maybe DOMRectReadOnly
forall a. Maybe a
Nothing
{-# INLINE noDOMRectReadOnly #-}

gTypeDOMRectReadOnly :: JSM GType
gTypeDOMRectReadOnly :: JSM GType
gTypeDOMRectReadOnly = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMRectReadOnly"

-- | Functions for this inteface are in "JSDOM.DOMStringList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMStringList Mozilla DOMStringList documentation>
newtype DOMStringList = DOMStringList { DOMStringList -> JSVal
unDOMStringList :: JSVal }

instance PToJSVal DOMStringList where
  pToJSVal :: DOMStringList -> JSVal
pToJSVal = DOMStringList -> JSVal
unDOMStringList
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMStringList where
  pFromJSVal :: JSVal -> DOMStringList
pFromJSVal = JSVal -> DOMStringList
DOMStringList
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMStringList where
  toJSVal :: DOMStringList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMStringList -> JSVal) -> DOMStringList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMStringList -> JSVal
unDOMStringList
  {-# INLINE toJSVal #-}

instance FromJSVal DOMStringList where
  fromJSVal :: JSVal -> JSM (Maybe DOMStringList)
fromJSVal JSVal
v = (JSVal -> DOMStringList) -> Maybe JSVal -> Maybe DOMStringList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMStringList
DOMStringList (Maybe JSVal -> Maybe DOMStringList)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMStringList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMStringList
fromJSValUnchecked = DOMStringList -> JSM DOMStringList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMStringList -> JSM DOMStringList)
-> (JSVal -> DOMStringList) -> JSVal -> JSM DOMStringList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMStringList
DOMStringList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMStringList where
  makeObject :: DOMStringList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMStringList -> JSVal) -> DOMStringList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMStringList -> JSVal
unDOMStringList

instance IsGObject DOMStringList where
  typeGType :: DOMStringList -> JSM GType
typeGType DOMStringList
_ = JSM GType
gTypeDOMStringList
  {-# INLINE typeGType #-}

noDOMStringList :: Maybe DOMStringList
noDOMStringList :: Maybe DOMStringList
noDOMStringList = Maybe DOMStringList
forall a. Maybe a
Nothing
{-# INLINE noDOMStringList #-}

gTypeDOMStringList :: JSM GType
gTypeDOMStringList :: JSM GType
gTypeDOMStringList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMStringList"

-- | Functions for this inteface are in "JSDOM.DOMStringMap".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMStringMap Mozilla DOMStringMap documentation>
newtype DOMStringMap = DOMStringMap { DOMStringMap -> JSVal
unDOMStringMap :: JSVal }

instance PToJSVal DOMStringMap where
  pToJSVal :: DOMStringMap -> JSVal
pToJSVal = DOMStringMap -> JSVal
unDOMStringMap
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMStringMap where
  pFromJSVal :: JSVal -> DOMStringMap
pFromJSVal = JSVal -> DOMStringMap
DOMStringMap
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMStringMap where
  toJSVal :: DOMStringMap -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMStringMap -> JSVal) -> DOMStringMap -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMStringMap -> JSVal
unDOMStringMap
  {-# INLINE toJSVal #-}

instance FromJSVal DOMStringMap where
  fromJSVal :: JSVal -> JSM (Maybe DOMStringMap)
fromJSVal JSVal
v = (JSVal -> DOMStringMap) -> Maybe JSVal -> Maybe DOMStringMap
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMStringMap
DOMStringMap (Maybe JSVal -> Maybe DOMStringMap)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMStringMap)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMStringMap
fromJSValUnchecked = DOMStringMap -> JSM DOMStringMap
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMStringMap -> JSM DOMStringMap)
-> (JSVal -> DOMStringMap) -> JSVal -> JSM DOMStringMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMStringMap
DOMStringMap
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMStringMap where
  makeObject :: DOMStringMap -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMStringMap -> JSVal) -> DOMStringMap -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMStringMap -> JSVal
unDOMStringMap

instance IsGObject DOMStringMap where
  typeGType :: DOMStringMap -> JSM GType
typeGType DOMStringMap
_ = JSM GType
gTypeDOMStringMap
  {-# INLINE typeGType #-}

noDOMStringMap :: Maybe DOMStringMap
noDOMStringMap :: Maybe DOMStringMap
noDOMStringMap = Maybe DOMStringMap
forall a. Maybe a
Nothing
{-# INLINE noDOMStringMap #-}

gTypeDOMStringMap :: JSM GType
gTypeDOMStringMap :: JSM GType
gTypeDOMStringMap = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMStringMap"

-- | Functions for this inteface are in "JSDOM.DOMTokenList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DOMTokenList Mozilla DOMTokenList documentation>
newtype DOMTokenList = DOMTokenList { DOMTokenList -> JSVal
unDOMTokenList :: JSVal }

instance PToJSVal DOMTokenList where
  pToJSVal :: DOMTokenList -> JSVal
pToJSVal = DOMTokenList -> JSVal
unDOMTokenList
  {-# INLINE pToJSVal #-}

instance PFromJSVal DOMTokenList where
  pFromJSVal :: JSVal -> DOMTokenList
pFromJSVal = JSVal -> DOMTokenList
DOMTokenList
  {-# INLINE pFromJSVal #-}

instance ToJSVal DOMTokenList where
  toJSVal :: DOMTokenList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DOMTokenList -> JSVal) -> DOMTokenList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMTokenList -> JSVal
unDOMTokenList
  {-# INLINE toJSVal #-}

instance FromJSVal DOMTokenList where
  fromJSVal :: JSVal -> JSM (Maybe DOMTokenList)
fromJSVal JSVal
v = (JSVal -> DOMTokenList) -> Maybe JSVal -> Maybe DOMTokenList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DOMTokenList
DOMTokenList (Maybe JSVal -> Maybe DOMTokenList)
-> JSM (Maybe JSVal) -> JSM (Maybe DOMTokenList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DOMTokenList
fromJSValUnchecked = DOMTokenList -> JSM DOMTokenList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DOMTokenList -> JSM DOMTokenList)
-> (JSVal -> DOMTokenList) -> JSVal -> JSM DOMTokenList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DOMTokenList
DOMTokenList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DOMTokenList where
  makeObject :: DOMTokenList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DOMTokenList -> JSVal) -> DOMTokenList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DOMTokenList -> JSVal
unDOMTokenList

instance IsGObject DOMTokenList where
  typeGType :: DOMTokenList -> JSM GType
typeGType DOMTokenList
_ = JSM GType
gTypeDOMTokenList
  {-# INLINE typeGType #-}

noDOMTokenList :: Maybe DOMTokenList
noDOMTokenList :: Maybe DOMTokenList
noDOMTokenList = Maybe DOMTokenList
forall a. Maybe a
Nothing
{-# INLINE noDOMTokenList #-}

gTypeDOMTokenList :: JSM GType
gTypeDOMTokenList :: JSM GType
gTypeDOMTokenList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DOMTokenList"

-- | Functions for this inteface are in "JSDOM.DataCue".
-- Base interface functions are in:
--
--     * "JSDOM.TextTrackCue"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitDataCue Mozilla WebKitDataCue documentation>
newtype DataCue = DataCue { DataCue -> JSVal
unDataCue :: JSVal }

instance PToJSVal DataCue where
  pToJSVal :: DataCue -> JSVal
pToJSVal = DataCue -> JSVal
unDataCue
  {-# INLINE pToJSVal #-}

instance PFromJSVal DataCue where
  pFromJSVal :: JSVal -> DataCue
pFromJSVal = JSVal -> DataCue
DataCue
  {-# INLINE pFromJSVal #-}

instance ToJSVal DataCue where
  toJSVal :: DataCue -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (DataCue -> JSVal) -> DataCue -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataCue -> JSVal
unDataCue
  {-# INLINE toJSVal #-}

instance FromJSVal DataCue where
  fromJSVal :: JSVal -> JSM (Maybe DataCue)
fromJSVal JSVal
v = (JSVal -> DataCue) -> Maybe JSVal -> Maybe DataCue
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DataCue
DataCue (Maybe JSVal -> Maybe DataCue)
-> JSM (Maybe JSVal) -> JSM (Maybe DataCue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DataCue
fromJSValUnchecked = DataCue -> JSM DataCue
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DataCue -> JSM DataCue)
-> (JSVal -> DataCue) -> JSVal -> JSM DataCue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DataCue
DataCue
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DataCue where
  makeObject :: DataCue -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DataCue -> JSVal) -> DataCue -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataCue -> JSVal
unDataCue

instance IsTextTrackCue DataCue
instance IsEventTarget DataCue
instance IsGObject DataCue where
  typeGType :: DataCue -> JSM GType
typeGType DataCue
_ = JSM GType
gTypeDataCue
  {-# INLINE typeGType #-}

noDataCue :: Maybe DataCue
noDataCue :: Maybe DataCue
noDataCue = Maybe DataCue
forall a. Maybe a
Nothing
{-# INLINE noDataCue #-}

gTypeDataCue :: JSM GType
gTypeDataCue :: JSM GType
gTypeDataCue = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitDataCue"

-- | Functions for this inteface are in "JSDOM.DataTransfer".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DataTransfer Mozilla DataTransfer documentation>
newtype DataTransfer = DataTransfer { DataTransfer -> JSVal
unDataTransfer :: JSVal }

instance PToJSVal DataTransfer where
  pToJSVal :: DataTransfer -> JSVal
pToJSVal = DataTransfer -> JSVal
unDataTransfer
  {-# INLINE pToJSVal #-}

instance PFromJSVal DataTransfer where
  pFromJSVal :: JSVal -> DataTransfer
pFromJSVal = JSVal -> DataTransfer
DataTransfer
  {-# INLINE pFromJSVal #-}

instance ToJSVal DataTransfer where
  toJSVal :: DataTransfer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DataTransfer -> JSVal) -> DataTransfer -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataTransfer -> JSVal
unDataTransfer
  {-# INLINE toJSVal #-}

instance FromJSVal DataTransfer where
  fromJSVal :: JSVal -> JSM (Maybe DataTransfer)
fromJSVal JSVal
v = (JSVal -> DataTransfer) -> Maybe JSVal -> Maybe DataTransfer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DataTransfer
DataTransfer (Maybe JSVal -> Maybe DataTransfer)
-> JSM (Maybe JSVal) -> JSM (Maybe DataTransfer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DataTransfer
fromJSValUnchecked = DataTransfer -> JSM DataTransfer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DataTransfer -> JSM DataTransfer)
-> (JSVal -> DataTransfer) -> JSVal -> JSM DataTransfer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DataTransfer
DataTransfer
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DataTransfer where
  makeObject :: DataTransfer -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DataTransfer -> JSVal) -> DataTransfer -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataTransfer -> JSVal
unDataTransfer

instance IsGObject DataTransfer where
  typeGType :: DataTransfer -> JSM GType
typeGType DataTransfer
_ = JSM GType
gTypeDataTransfer
  {-# INLINE typeGType #-}

noDataTransfer :: Maybe DataTransfer
noDataTransfer :: Maybe DataTransfer
noDataTransfer = Maybe DataTransfer
forall a. Maybe a
Nothing
{-# INLINE noDataTransfer #-}

gTypeDataTransfer :: JSM GType
gTypeDataTransfer :: JSM GType
gTypeDataTransfer = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DataTransfer"

-- | Functions for this inteface are in "JSDOM.DataTransferItem".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DataTransferItem Mozilla DataTransferItem documentation>
newtype DataTransferItem = DataTransferItem { DataTransferItem -> JSVal
unDataTransferItem :: JSVal }

instance PToJSVal DataTransferItem where
  pToJSVal :: DataTransferItem -> JSVal
pToJSVal = DataTransferItem -> JSVal
unDataTransferItem
  {-# INLINE pToJSVal #-}

instance PFromJSVal DataTransferItem where
  pFromJSVal :: JSVal -> DataTransferItem
pFromJSVal = JSVal -> DataTransferItem
DataTransferItem
  {-# INLINE pFromJSVal #-}

instance ToJSVal DataTransferItem where
  toJSVal :: DataTransferItem -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DataTransferItem -> JSVal) -> DataTransferItem -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataTransferItem -> JSVal
unDataTransferItem
  {-# INLINE toJSVal #-}

instance FromJSVal DataTransferItem where
  fromJSVal :: JSVal -> JSM (Maybe DataTransferItem)
fromJSVal JSVal
v = (JSVal -> DataTransferItem)
-> Maybe JSVal -> Maybe DataTransferItem
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DataTransferItem
DataTransferItem (Maybe JSVal -> Maybe DataTransferItem)
-> JSM (Maybe JSVal) -> JSM (Maybe DataTransferItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DataTransferItem
fromJSValUnchecked = DataTransferItem -> JSM DataTransferItem
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DataTransferItem -> JSM DataTransferItem)
-> (JSVal -> DataTransferItem) -> JSVal -> JSM DataTransferItem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DataTransferItem
DataTransferItem
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DataTransferItem where
  makeObject :: DataTransferItem -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DataTransferItem -> JSVal) -> DataTransferItem -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataTransferItem -> JSVal
unDataTransferItem

instance IsGObject DataTransferItem where
  typeGType :: DataTransferItem -> JSM GType
typeGType DataTransferItem
_ = JSM GType
gTypeDataTransferItem
  {-# INLINE typeGType #-}

noDataTransferItem :: Maybe DataTransferItem
noDataTransferItem :: Maybe DataTransferItem
noDataTransferItem = Maybe DataTransferItem
forall a. Maybe a
Nothing
{-# INLINE noDataTransferItem #-}

gTypeDataTransferItem :: JSM GType
gTypeDataTransferItem :: JSM GType
gTypeDataTransferItem = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DataTransferItem"

-- | Functions for this inteface are in "JSDOM.DataTransferItemList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DataTransferItemList Mozilla DataTransferItemList documentation>
newtype DataTransferItemList = DataTransferItemList { DataTransferItemList -> JSVal
unDataTransferItemList :: JSVal }

instance PToJSVal DataTransferItemList where
  pToJSVal :: DataTransferItemList -> JSVal
pToJSVal = DataTransferItemList -> JSVal
unDataTransferItemList
  {-# INLINE pToJSVal #-}

instance PFromJSVal DataTransferItemList where
  pFromJSVal :: JSVal -> DataTransferItemList
pFromJSVal = JSVal -> DataTransferItemList
DataTransferItemList
  {-# INLINE pFromJSVal #-}

instance ToJSVal DataTransferItemList where
  toJSVal :: DataTransferItemList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DataTransferItemList -> JSVal)
-> DataTransferItemList
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataTransferItemList -> JSVal
unDataTransferItemList
  {-# INLINE toJSVal #-}

instance FromJSVal DataTransferItemList where
  fromJSVal :: JSVal -> JSM (Maybe DataTransferItemList)
fromJSVal JSVal
v = (JSVal -> DataTransferItemList)
-> Maybe JSVal -> Maybe DataTransferItemList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DataTransferItemList
DataTransferItemList (Maybe JSVal -> Maybe DataTransferItemList)
-> JSM (Maybe JSVal) -> JSM (Maybe DataTransferItemList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DataTransferItemList
fromJSValUnchecked = DataTransferItemList -> JSM DataTransferItemList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DataTransferItemList -> JSM DataTransferItemList)
-> (JSVal -> DataTransferItemList)
-> JSVal
-> JSM DataTransferItemList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DataTransferItemList
DataTransferItemList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DataTransferItemList where
  makeObject :: DataTransferItemList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DataTransferItemList -> JSVal)
-> DataTransferItemList
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataTransferItemList -> JSVal
unDataTransferItemList

instance IsGObject DataTransferItemList where
  typeGType :: DataTransferItemList -> JSM GType
typeGType DataTransferItemList
_ = JSM GType
gTypeDataTransferItemList
  {-# INLINE typeGType #-}

noDataTransferItemList :: Maybe DataTransferItemList
noDataTransferItemList :: Maybe DataTransferItemList
noDataTransferItemList = Maybe DataTransferItemList
forall a. Maybe a
Nothing
{-# INLINE noDataTransferItemList #-}

gTypeDataTransferItemList :: JSM GType
gTypeDataTransferItemList :: JSM GType
gTypeDataTransferItemList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DataTransferItemList"

-- | Functions for this inteface are in "JSDOM.Database".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Database Mozilla Database documentation>
newtype Database = Database { Database -> JSVal
unDatabase :: JSVal }

instance PToJSVal Database where
  pToJSVal :: Database -> JSVal
pToJSVal = Database -> JSVal
unDatabase
  {-# INLINE pToJSVal #-}

instance PFromJSVal Database where
  pFromJSVal :: JSVal -> Database
pFromJSVal = JSVal -> Database
Database
  {-# INLINE pFromJSVal #-}

instance ToJSVal Database where
  toJSVal :: Database -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Database -> JSVal) -> Database -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Database -> JSVal
unDatabase
  {-# INLINE toJSVal #-}

instance FromJSVal Database where
  fromJSVal :: JSVal -> JSM (Maybe Database)
fromJSVal JSVal
v = (JSVal -> Database) -> Maybe JSVal -> Maybe Database
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Database
Database (Maybe JSVal -> Maybe Database)
-> JSM (Maybe JSVal) -> JSM (Maybe Database)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Database
fromJSValUnchecked = Database -> JSM Database
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Database -> JSM Database)
-> (JSVal -> Database) -> JSVal -> JSM Database
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Database
Database
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Database where
  makeObject :: Database -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Database -> JSVal) -> Database -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Database -> JSVal
unDatabase

instance IsGObject Database where
  typeGType :: Database -> JSM GType
typeGType Database
_ = JSM GType
gTypeDatabase
  {-# INLINE typeGType #-}

noDatabase :: Maybe Database
noDatabase :: Maybe Database
noDatabase = Maybe Database
forall a. Maybe a
Nothing
{-# INLINE noDatabase #-}

gTypeDatabase :: JSM GType
gTypeDatabase :: JSM GType
gTypeDatabase = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Database"

-- | Functions for this inteface are in "JSDOM.DedicatedWorkerGlobalScope".
-- Base interface functions are in:
--
--     * "JSDOM.WorkerGlobalScope"
--     * "JSDOM.EventTarget"
--     * "JSDOM.WindowOrWorkerGlobalScope"
--     * "JSDOM.GlobalPerformance"
--     * "JSDOM.GlobalCrypto"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DedicatedWorkerGlobalScope Mozilla DedicatedWorkerGlobalScope documentation>
newtype DedicatedWorkerGlobalScope = DedicatedWorkerGlobalScope { DedicatedWorkerGlobalScope -> JSVal
unDedicatedWorkerGlobalScope :: JSVal }

instance PToJSVal DedicatedWorkerGlobalScope where
  pToJSVal :: DedicatedWorkerGlobalScope -> JSVal
pToJSVal = DedicatedWorkerGlobalScope -> JSVal
unDedicatedWorkerGlobalScope
  {-# INLINE pToJSVal #-}

instance PFromJSVal DedicatedWorkerGlobalScope where
  pFromJSVal :: JSVal -> DedicatedWorkerGlobalScope
pFromJSVal = JSVal -> DedicatedWorkerGlobalScope
DedicatedWorkerGlobalScope
  {-# INLINE pFromJSVal #-}

instance ToJSVal DedicatedWorkerGlobalScope where
  toJSVal :: DedicatedWorkerGlobalScope -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DedicatedWorkerGlobalScope -> JSVal)
-> DedicatedWorkerGlobalScope
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DedicatedWorkerGlobalScope -> JSVal
unDedicatedWorkerGlobalScope
  {-# INLINE toJSVal #-}

instance FromJSVal DedicatedWorkerGlobalScope where
  fromJSVal :: JSVal -> JSM (Maybe DedicatedWorkerGlobalScope)
fromJSVal JSVal
v = (JSVal -> DedicatedWorkerGlobalScope)
-> Maybe JSVal -> Maybe DedicatedWorkerGlobalScope
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DedicatedWorkerGlobalScope
DedicatedWorkerGlobalScope (Maybe JSVal -> Maybe DedicatedWorkerGlobalScope)
-> JSM (Maybe JSVal) -> JSM (Maybe DedicatedWorkerGlobalScope)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DedicatedWorkerGlobalScope
fromJSValUnchecked = DedicatedWorkerGlobalScope -> JSM DedicatedWorkerGlobalScope
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DedicatedWorkerGlobalScope -> JSM DedicatedWorkerGlobalScope)
-> (JSVal -> DedicatedWorkerGlobalScope)
-> JSVal
-> JSM DedicatedWorkerGlobalScope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DedicatedWorkerGlobalScope
DedicatedWorkerGlobalScope
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DedicatedWorkerGlobalScope where
  makeObject :: DedicatedWorkerGlobalScope -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DedicatedWorkerGlobalScope -> JSVal)
-> DedicatedWorkerGlobalScope
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DedicatedWorkerGlobalScope -> JSVal
unDedicatedWorkerGlobalScope

instance IsWorkerGlobalScope DedicatedWorkerGlobalScope
instance IsEventTarget DedicatedWorkerGlobalScope
instance IsWindowOrWorkerGlobalScope DedicatedWorkerGlobalScope
instance IsGlobalPerformance DedicatedWorkerGlobalScope
instance IsGlobalCrypto DedicatedWorkerGlobalScope
instance IsGObject DedicatedWorkerGlobalScope where
  typeGType :: DedicatedWorkerGlobalScope -> JSM GType
typeGType DedicatedWorkerGlobalScope
_ = JSM GType
gTypeDedicatedWorkerGlobalScope
  {-# INLINE typeGType #-}

noDedicatedWorkerGlobalScope :: Maybe DedicatedWorkerGlobalScope
noDedicatedWorkerGlobalScope :: Maybe DedicatedWorkerGlobalScope
noDedicatedWorkerGlobalScope = Maybe DedicatedWorkerGlobalScope
forall a. Maybe a
Nothing
{-# INLINE noDedicatedWorkerGlobalScope #-}

gTypeDedicatedWorkerGlobalScope :: JSM GType
gTypeDedicatedWorkerGlobalScope :: JSM GType
gTypeDedicatedWorkerGlobalScope = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DedicatedWorkerGlobalScope"

-- | Functions for this inteface are in "JSDOM.DelayNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DelayNode Mozilla DelayNode documentation>
newtype DelayNode = DelayNode { DelayNode -> JSVal
unDelayNode :: JSVal }

instance PToJSVal DelayNode where
  pToJSVal :: DelayNode -> JSVal
pToJSVal = DelayNode -> JSVal
unDelayNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal DelayNode where
  pFromJSVal :: JSVal -> DelayNode
pFromJSVal = JSVal -> DelayNode
DelayNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal DelayNode where
  toJSVal :: DelayNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DelayNode -> JSVal) -> DelayNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DelayNode -> JSVal
unDelayNode
  {-# INLINE toJSVal #-}

instance FromJSVal DelayNode where
  fromJSVal :: JSVal -> JSM (Maybe DelayNode)
fromJSVal JSVal
v = (JSVal -> DelayNode) -> Maybe JSVal -> Maybe DelayNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DelayNode
DelayNode (Maybe JSVal -> Maybe DelayNode)
-> JSM (Maybe JSVal) -> JSM (Maybe DelayNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DelayNode
fromJSValUnchecked = DelayNode -> JSM DelayNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DelayNode -> JSM DelayNode)
-> (JSVal -> DelayNode) -> JSVal -> JSM DelayNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DelayNode
DelayNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DelayNode where
  makeObject :: DelayNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DelayNode -> JSVal) -> DelayNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DelayNode -> JSVal
unDelayNode

instance IsAudioNode DelayNode
instance IsEventTarget DelayNode
instance IsGObject DelayNode where
  typeGType :: DelayNode -> JSM GType
typeGType DelayNode
_ = JSM GType
gTypeDelayNode
  {-# INLINE typeGType #-}

noDelayNode :: Maybe DelayNode
noDelayNode :: Maybe DelayNode
noDelayNode = Maybe DelayNode
forall a. Maybe a
Nothing
{-# INLINE noDelayNode #-}

gTypeDelayNode :: JSM GType
gTypeDelayNode :: JSM GType
gTypeDelayNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DelayNode"

-- | Functions for this inteface are in "JSDOM.DeviceMotionEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DeviceMotionEvent Mozilla DeviceMotionEvent documentation>
newtype DeviceMotionEvent = DeviceMotionEvent { DeviceMotionEvent -> JSVal
unDeviceMotionEvent :: JSVal }

instance PToJSVal DeviceMotionEvent where
  pToJSVal :: DeviceMotionEvent -> JSVal
pToJSVal = DeviceMotionEvent -> JSVal
unDeviceMotionEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal DeviceMotionEvent where
  pFromJSVal :: JSVal -> DeviceMotionEvent
pFromJSVal = JSVal -> DeviceMotionEvent
DeviceMotionEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal DeviceMotionEvent where
  toJSVal :: DeviceMotionEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DeviceMotionEvent -> JSVal) -> DeviceMotionEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DeviceMotionEvent -> JSVal
unDeviceMotionEvent
  {-# INLINE toJSVal #-}

instance FromJSVal DeviceMotionEvent where
  fromJSVal :: JSVal -> JSM (Maybe DeviceMotionEvent)
fromJSVal JSVal
v = (JSVal -> DeviceMotionEvent)
-> Maybe JSVal -> Maybe DeviceMotionEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DeviceMotionEvent
DeviceMotionEvent (Maybe JSVal -> Maybe DeviceMotionEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe DeviceMotionEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DeviceMotionEvent
fromJSValUnchecked = DeviceMotionEvent -> JSM DeviceMotionEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DeviceMotionEvent -> JSM DeviceMotionEvent)
-> (JSVal -> DeviceMotionEvent) -> JSVal -> JSM DeviceMotionEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DeviceMotionEvent
DeviceMotionEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DeviceMotionEvent where
  makeObject :: DeviceMotionEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DeviceMotionEvent -> JSVal) -> DeviceMotionEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DeviceMotionEvent -> JSVal
unDeviceMotionEvent

instance IsEvent DeviceMotionEvent
instance IsGObject DeviceMotionEvent where
  typeGType :: DeviceMotionEvent -> JSM GType
typeGType DeviceMotionEvent
_ = JSM GType
gTypeDeviceMotionEvent
  {-# INLINE typeGType #-}

noDeviceMotionEvent :: Maybe DeviceMotionEvent
noDeviceMotionEvent :: Maybe DeviceMotionEvent
noDeviceMotionEvent = Maybe DeviceMotionEvent
forall a. Maybe a
Nothing
{-# INLINE noDeviceMotionEvent #-}

gTypeDeviceMotionEvent :: JSM GType
gTypeDeviceMotionEvent :: JSM GType
gTypeDeviceMotionEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DeviceMotionEvent"

-- | Functions for this inteface are in "JSDOM.DeviceOrientationEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DeviceOrientationEvent Mozilla DeviceOrientationEvent documentation>
newtype DeviceOrientationEvent = DeviceOrientationEvent { DeviceOrientationEvent -> JSVal
unDeviceOrientationEvent :: JSVal }

instance PToJSVal DeviceOrientationEvent where
  pToJSVal :: DeviceOrientationEvent -> JSVal
pToJSVal = DeviceOrientationEvent -> JSVal
unDeviceOrientationEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal DeviceOrientationEvent where
  pFromJSVal :: JSVal -> DeviceOrientationEvent
pFromJSVal = JSVal -> DeviceOrientationEvent
DeviceOrientationEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal DeviceOrientationEvent where
  toJSVal :: DeviceOrientationEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DeviceOrientationEvent -> JSVal)
-> DeviceOrientationEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DeviceOrientationEvent -> JSVal
unDeviceOrientationEvent
  {-# INLINE toJSVal #-}

instance FromJSVal DeviceOrientationEvent where
  fromJSVal :: JSVal -> JSM (Maybe DeviceOrientationEvent)
fromJSVal JSVal
v = (JSVal -> DeviceOrientationEvent)
-> Maybe JSVal -> Maybe DeviceOrientationEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DeviceOrientationEvent
DeviceOrientationEvent (Maybe JSVal -> Maybe DeviceOrientationEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe DeviceOrientationEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DeviceOrientationEvent
fromJSValUnchecked = DeviceOrientationEvent -> JSM DeviceOrientationEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DeviceOrientationEvent -> JSM DeviceOrientationEvent)
-> (JSVal -> DeviceOrientationEvent)
-> JSVal
-> JSM DeviceOrientationEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DeviceOrientationEvent
DeviceOrientationEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DeviceOrientationEvent where
  makeObject :: DeviceOrientationEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DeviceOrientationEvent -> JSVal)
-> DeviceOrientationEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DeviceOrientationEvent -> JSVal
unDeviceOrientationEvent

instance IsEvent DeviceOrientationEvent
instance IsGObject DeviceOrientationEvent where
  typeGType :: DeviceOrientationEvent -> JSM GType
typeGType DeviceOrientationEvent
_ = JSM GType
gTypeDeviceOrientationEvent
  {-# INLINE typeGType #-}

noDeviceOrientationEvent :: Maybe DeviceOrientationEvent
noDeviceOrientationEvent :: Maybe DeviceOrientationEvent
noDeviceOrientationEvent = Maybe DeviceOrientationEvent
forall a. Maybe a
Nothing
{-# INLINE noDeviceOrientationEvent #-}

gTypeDeviceOrientationEvent :: JSM GType
gTypeDeviceOrientationEvent :: JSM GType
gTypeDeviceOrientationEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DeviceOrientationEvent"

-- | Functions for this inteface are in "JSDOM.DeviceProximityEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DeviceProximityEvent Mozilla DeviceProximityEvent documentation>
newtype DeviceProximityEvent = DeviceProximityEvent { DeviceProximityEvent -> JSVal
unDeviceProximityEvent :: JSVal }

instance PToJSVal DeviceProximityEvent where
  pToJSVal :: DeviceProximityEvent -> JSVal
pToJSVal = DeviceProximityEvent -> JSVal
unDeviceProximityEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal DeviceProximityEvent where
  pFromJSVal :: JSVal -> DeviceProximityEvent
pFromJSVal = JSVal -> DeviceProximityEvent
DeviceProximityEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal DeviceProximityEvent where
  toJSVal :: DeviceProximityEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DeviceProximityEvent -> JSVal)
-> DeviceProximityEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DeviceProximityEvent -> JSVal
unDeviceProximityEvent
  {-# INLINE toJSVal #-}

instance FromJSVal DeviceProximityEvent where
  fromJSVal :: JSVal -> JSM (Maybe DeviceProximityEvent)
fromJSVal JSVal
v = (JSVal -> DeviceProximityEvent)
-> Maybe JSVal -> Maybe DeviceProximityEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DeviceProximityEvent
DeviceProximityEvent (Maybe JSVal -> Maybe DeviceProximityEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe DeviceProximityEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DeviceProximityEvent
fromJSValUnchecked = DeviceProximityEvent -> JSM DeviceProximityEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DeviceProximityEvent -> JSM DeviceProximityEvent)
-> (JSVal -> DeviceProximityEvent)
-> JSVal
-> JSM DeviceProximityEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DeviceProximityEvent
DeviceProximityEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DeviceProximityEvent where
  makeObject :: DeviceProximityEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DeviceProximityEvent -> JSVal)
-> DeviceProximityEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DeviceProximityEvent -> JSVal
unDeviceProximityEvent

instance IsEvent DeviceProximityEvent
instance IsGObject DeviceProximityEvent where
  typeGType :: DeviceProximityEvent -> JSM GType
typeGType DeviceProximityEvent
_ = JSM GType
gTypeDeviceProximityEvent
  {-# INLINE typeGType #-}

noDeviceProximityEvent :: Maybe DeviceProximityEvent
noDeviceProximityEvent :: Maybe DeviceProximityEvent
noDeviceProximityEvent = Maybe DeviceProximityEvent
forall a. Maybe a
Nothing
{-# INLINE noDeviceProximityEvent #-}

gTypeDeviceProximityEvent :: JSM GType
gTypeDeviceProximityEvent :: JSM GType
gTypeDeviceProximityEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DeviceProximityEvent"

-- | Functions for this inteface are in "JSDOM.DeviceProximityEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DeviceProximityEventInit Mozilla DeviceProximityEventInit documentation>
newtype DeviceProximityEventInit = DeviceProximityEventInit { DeviceProximityEventInit -> JSVal
unDeviceProximityEventInit :: JSVal }

instance PToJSVal DeviceProximityEventInit where
  pToJSVal :: DeviceProximityEventInit -> JSVal
pToJSVal = DeviceProximityEventInit -> JSVal
unDeviceProximityEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal DeviceProximityEventInit where
  pFromJSVal :: JSVal -> DeviceProximityEventInit
pFromJSVal = JSVal -> DeviceProximityEventInit
DeviceProximityEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal DeviceProximityEventInit where
  toJSVal :: DeviceProximityEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DeviceProximityEventInit -> JSVal)
-> DeviceProximityEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DeviceProximityEventInit -> JSVal
unDeviceProximityEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal DeviceProximityEventInit where
  fromJSVal :: JSVal -> JSM (Maybe DeviceProximityEventInit)
fromJSVal JSVal
v = (JSVal -> DeviceProximityEventInit)
-> Maybe JSVal -> Maybe DeviceProximityEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DeviceProximityEventInit
DeviceProximityEventInit (Maybe JSVal -> Maybe DeviceProximityEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe DeviceProximityEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DeviceProximityEventInit
fromJSValUnchecked = DeviceProximityEventInit -> JSM DeviceProximityEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DeviceProximityEventInit -> JSM DeviceProximityEventInit)
-> (JSVal -> DeviceProximityEventInit)
-> JSVal
-> JSM DeviceProximityEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DeviceProximityEventInit
DeviceProximityEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DeviceProximityEventInit where
  makeObject :: DeviceProximityEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DeviceProximityEventInit -> JSVal)
-> DeviceProximityEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DeviceProximityEventInit -> JSVal
unDeviceProximityEventInit

instance IsEventInit DeviceProximityEventInit
instance IsGObject DeviceProximityEventInit where
  typeGType :: DeviceProximityEventInit -> JSM GType
typeGType DeviceProximityEventInit
_ = JSM GType
gTypeDeviceProximityEventInit
  {-# INLINE typeGType #-}

noDeviceProximityEventInit :: Maybe DeviceProximityEventInit
noDeviceProximityEventInit :: Maybe DeviceProximityEventInit
noDeviceProximityEventInit = Maybe DeviceProximityEventInit
forall a. Maybe a
Nothing
{-# INLINE noDeviceProximityEventInit #-}

gTypeDeviceProximityEventInit :: JSM GType
gTypeDeviceProximityEventInit :: JSM GType
gTypeDeviceProximityEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DeviceProximityEventInit"

-- | Functions for this inteface are in "JSDOM.Document".
-- Base interface functions are in:
--
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.DocumentOrShadowRoot"
--     * "JSDOM.NonElementParentNode"
--     * "JSDOM.ParentNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Document Mozilla Document documentation>
newtype Document = Document { Document -> JSVal
unDocument :: JSVal }

instance PToJSVal Document where
  pToJSVal :: Document -> JSVal
pToJSVal = Document -> JSVal
unDocument
  {-# INLINE pToJSVal #-}

instance PFromJSVal Document where
  pFromJSVal :: JSVal -> Document
pFromJSVal = JSVal -> Document
Document
  {-# INLINE pFromJSVal #-}

instance ToJSVal Document where
  toJSVal :: Document -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Document -> JSVal) -> Document -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Document -> JSVal
unDocument
  {-# INLINE toJSVal #-}

instance FromJSVal Document where
  fromJSVal :: JSVal -> JSM (Maybe Document)
fromJSVal JSVal
v = (JSVal -> Document) -> Maybe JSVal -> Maybe Document
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Document
Document (Maybe JSVal -> Maybe Document)
-> JSM (Maybe JSVal) -> JSM (Maybe Document)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Document
fromJSValUnchecked = Document -> JSM Document
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Document -> JSM Document)
-> (JSVal -> Document) -> JSVal -> JSM Document
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Document
Document
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Document where
  makeObject :: Document -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Document -> JSVal) -> Document -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Document -> JSVal
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 :: forall o. IsDocument o => o -> Document
toDocument = JSVal -> Document
Document (JSVal -> Document) -> (o -> JSVal) -> o -> Document
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: Document -> JSM GType
typeGType Document
_ = JSM GType
gTypeDocument
  {-# INLINE typeGType #-}

noDocument :: Maybe Document
noDocument :: Maybe Document
noDocument = Maybe Document
forall a. Maybe a
Nothing
{-# INLINE noDocument #-}

gTypeDocument :: JSM GType
gTypeDocument :: JSM GType
gTypeDocument = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Document"

-- | Functions for this inteface are in "JSDOM.DocumentAndElementEventHandlers".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DocumentAndElementEventHandlers Mozilla DocumentAndElementEventHandlers documentation>
newtype DocumentAndElementEventHandlers = DocumentAndElementEventHandlers { DocumentAndElementEventHandlers -> JSVal
unDocumentAndElementEventHandlers :: JSVal }

instance PToJSVal DocumentAndElementEventHandlers where
  pToJSVal :: DocumentAndElementEventHandlers -> JSVal
pToJSVal = DocumentAndElementEventHandlers -> JSVal
unDocumentAndElementEventHandlers
  {-# INLINE pToJSVal #-}

instance PFromJSVal DocumentAndElementEventHandlers where
  pFromJSVal :: JSVal -> DocumentAndElementEventHandlers
pFromJSVal = JSVal -> DocumentAndElementEventHandlers
DocumentAndElementEventHandlers
  {-# INLINE pFromJSVal #-}

instance ToJSVal DocumentAndElementEventHandlers where
  toJSVal :: DocumentAndElementEventHandlers -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DocumentAndElementEventHandlers -> JSVal)
-> DocumentAndElementEventHandlers
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocumentAndElementEventHandlers -> JSVal
unDocumentAndElementEventHandlers
  {-# INLINE toJSVal #-}

instance FromJSVal DocumentAndElementEventHandlers where
  fromJSVal :: JSVal -> JSM (Maybe DocumentAndElementEventHandlers)
fromJSVal JSVal
v = (JSVal -> DocumentAndElementEventHandlers)
-> Maybe JSVal -> Maybe DocumentAndElementEventHandlers
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DocumentAndElementEventHandlers
DocumentAndElementEventHandlers (Maybe JSVal -> Maybe DocumentAndElementEventHandlers)
-> JSM (Maybe JSVal) -> JSM (Maybe DocumentAndElementEventHandlers)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DocumentAndElementEventHandlers
fromJSValUnchecked = DocumentAndElementEventHandlers
-> JSM DocumentAndElementEventHandlers
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DocumentAndElementEventHandlers
 -> JSM DocumentAndElementEventHandlers)
-> (JSVal -> DocumentAndElementEventHandlers)
-> JSVal
-> JSM DocumentAndElementEventHandlers
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DocumentAndElementEventHandlers
DocumentAndElementEventHandlers
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DocumentAndElementEventHandlers where
  makeObject :: DocumentAndElementEventHandlers -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DocumentAndElementEventHandlers -> JSVal)
-> DocumentAndElementEventHandlers
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocumentAndElementEventHandlers -> JSVal
unDocumentAndElementEventHandlers

class (IsGObject o) => IsDocumentAndElementEventHandlers o
toDocumentAndElementEventHandlers :: IsDocumentAndElementEventHandlers o => o -> DocumentAndElementEventHandlers
toDocumentAndElementEventHandlers :: forall o.
IsDocumentAndElementEventHandlers o =>
o -> DocumentAndElementEventHandlers
toDocumentAndElementEventHandlers = JSVal -> DocumentAndElementEventHandlers
DocumentAndElementEventHandlers (JSVal -> DocumentAndElementEventHandlers)
-> (o -> JSVal) -> o -> DocumentAndElementEventHandlers
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsDocumentAndElementEventHandlers DocumentAndElementEventHandlers
instance IsGObject DocumentAndElementEventHandlers where
  typeGType :: DocumentAndElementEventHandlers -> JSM GType
typeGType DocumentAndElementEventHandlers
_ = JSM GType
gTypeDocumentAndElementEventHandlers
  {-# INLINE typeGType #-}

noDocumentAndElementEventHandlers :: Maybe DocumentAndElementEventHandlers
noDocumentAndElementEventHandlers :: Maybe DocumentAndElementEventHandlers
noDocumentAndElementEventHandlers = Maybe DocumentAndElementEventHandlers
forall a. Maybe a
Nothing
{-# INLINE noDocumentAndElementEventHandlers #-}

gTypeDocumentAndElementEventHandlers :: JSM GType
gTypeDocumentAndElementEventHandlers :: JSM GType
gTypeDocumentAndElementEventHandlers = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DocumentAndElementEventHandlers"

-- | Functions for this inteface are in "JSDOM.DocumentFragment".
-- Base interface functions are in:
--
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.NonElementParentNode"
--     * "JSDOM.ParentNode"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DocumentFragment Mozilla DocumentFragment documentation>
newtype DocumentFragment = DocumentFragment { DocumentFragment -> JSVal
unDocumentFragment :: JSVal }

instance PToJSVal DocumentFragment where
  pToJSVal :: DocumentFragment -> JSVal
pToJSVal = DocumentFragment -> JSVal
unDocumentFragment
  {-# INLINE pToJSVal #-}

instance PFromJSVal DocumentFragment where
  pFromJSVal :: JSVal -> DocumentFragment
pFromJSVal = JSVal -> DocumentFragment
DocumentFragment
  {-# INLINE pFromJSVal #-}

instance ToJSVal DocumentFragment where
  toJSVal :: DocumentFragment -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DocumentFragment -> JSVal) -> DocumentFragment -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocumentFragment -> JSVal
unDocumentFragment
  {-# INLINE toJSVal #-}

instance FromJSVal DocumentFragment where
  fromJSVal :: JSVal -> JSM (Maybe DocumentFragment)
fromJSVal JSVal
v = (JSVal -> DocumentFragment)
-> Maybe JSVal -> Maybe DocumentFragment
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DocumentFragment
DocumentFragment (Maybe JSVal -> Maybe DocumentFragment)
-> JSM (Maybe JSVal) -> JSM (Maybe DocumentFragment)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DocumentFragment
fromJSValUnchecked = DocumentFragment -> JSM DocumentFragment
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DocumentFragment -> JSM DocumentFragment)
-> (JSVal -> DocumentFragment) -> JSVal -> JSM DocumentFragment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DocumentFragment
DocumentFragment
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DocumentFragment where
  makeObject :: DocumentFragment -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DocumentFragment -> JSVal) -> DocumentFragment -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocumentFragment -> JSVal
unDocumentFragment

class (IsNode o, IsEventTarget o, IsNonElementParentNode o, IsParentNode o, IsGObject o) => IsDocumentFragment o
toDocumentFragment :: IsDocumentFragment o => o -> DocumentFragment
toDocumentFragment :: forall o. IsDocumentFragment o => o -> DocumentFragment
toDocumentFragment = JSVal -> DocumentFragment
DocumentFragment (JSVal -> DocumentFragment)
-> (o -> JSVal) -> o -> DocumentFragment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsDocumentFragment DocumentFragment
instance IsNode DocumentFragment
instance IsEventTarget DocumentFragment
instance IsNonElementParentNode DocumentFragment
instance IsParentNode DocumentFragment
instance IsGObject DocumentFragment where
  typeGType :: DocumentFragment -> JSM GType
typeGType DocumentFragment
_ = JSM GType
gTypeDocumentFragment
  {-# INLINE typeGType #-}

noDocumentFragment :: Maybe DocumentFragment
noDocumentFragment :: Maybe DocumentFragment
noDocumentFragment = Maybe DocumentFragment
forall a. Maybe a
Nothing
{-# INLINE noDocumentFragment #-}

gTypeDocumentFragment :: JSM GType
gTypeDocumentFragment :: JSM GType
gTypeDocumentFragment = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DocumentFragment"

-- | Functions for this inteface are in "JSDOM.DocumentOrShadowRoot".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DocumentOrShadowRoot Mozilla DocumentOrShadowRoot documentation>
newtype DocumentOrShadowRoot = DocumentOrShadowRoot { DocumentOrShadowRoot -> JSVal
unDocumentOrShadowRoot :: JSVal }

instance PToJSVal DocumentOrShadowRoot where
  pToJSVal :: DocumentOrShadowRoot -> JSVal
pToJSVal = DocumentOrShadowRoot -> JSVal
unDocumentOrShadowRoot
  {-# INLINE pToJSVal #-}

instance PFromJSVal DocumentOrShadowRoot where
  pFromJSVal :: JSVal -> DocumentOrShadowRoot
pFromJSVal = JSVal -> DocumentOrShadowRoot
DocumentOrShadowRoot
  {-# INLINE pFromJSVal #-}

instance ToJSVal DocumentOrShadowRoot where
  toJSVal :: DocumentOrShadowRoot -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DocumentOrShadowRoot -> JSVal)
-> DocumentOrShadowRoot
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocumentOrShadowRoot -> JSVal
unDocumentOrShadowRoot
  {-# INLINE toJSVal #-}

instance FromJSVal DocumentOrShadowRoot where
  fromJSVal :: JSVal -> JSM (Maybe DocumentOrShadowRoot)
fromJSVal JSVal
v = (JSVal -> DocumentOrShadowRoot)
-> Maybe JSVal -> Maybe DocumentOrShadowRoot
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DocumentOrShadowRoot
DocumentOrShadowRoot (Maybe JSVal -> Maybe DocumentOrShadowRoot)
-> JSM (Maybe JSVal) -> JSM (Maybe DocumentOrShadowRoot)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DocumentOrShadowRoot
fromJSValUnchecked = DocumentOrShadowRoot -> JSM DocumentOrShadowRoot
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DocumentOrShadowRoot -> JSM DocumentOrShadowRoot)
-> (JSVal -> DocumentOrShadowRoot)
-> JSVal
-> JSM DocumentOrShadowRoot
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DocumentOrShadowRoot
DocumentOrShadowRoot
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DocumentOrShadowRoot where
  makeObject :: DocumentOrShadowRoot -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DocumentOrShadowRoot -> JSVal)
-> DocumentOrShadowRoot
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocumentOrShadowRoot -> JSVal
unDocumentOrShadowRoot

class (IsGObject o) => IsDocumentOrShadowRoot o
toDocumentOrShadowRoot :: IsDocumentOrShadowRoot o => o -> DocumentOrShadowRoot
toDocumentOrShadowRoot :: forall o. IsDocumentOrShadowRoot o => o -> DocumentOrShadowRoot
toDocumentOrShadowRoot = JSVal -> DocumentOrShadowRoot
DocumentOrShadowRoot (JSVal -> DocumentOrShadowRoot)
-> (o -> JSVal) -> o -> DocumentOrShadowRoot
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsDocumentOrShadowRoot DocumentOrShadowRoot
instance IsGObject DocumentOrShadowRoot where
  typeGType :: DocumentOrShadowRoot -> JSM GType
typeGType DocumentOrShadowRoot
_ = JSM GType
gTypeDocumentOrShadowRoot
  {-# INLINE typeGType #-}

noDocumentOrShadowRoot :: Maybe DocumentOrShadowRoot
noDocumentOrShadowRoot :: Maybe DocumentOrShadowRoot
noDocumentOrShadowRoot = Maybe DocumentOrShadowRoot
forall a. Maybe a
Nothing
{-# INLINE noDocumentOrShadowRoot #-}

gTypeDocumentOrShadowRoot :: JSM GType
gTypeDocumentOrShadowRoot :: JSM GType
gTypeDocumentOrShadowRoot = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DocumentOrShadowRoot"

-- | Functions for this inteface are in "JSDOM.DocumentTimeline".
-- Base interface functions are in:
--
--     * "JSDOM.AnimationTimeline"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DocumentTimeline Mozilla DocumentTimeline documentation>
newtype DocumentTimeline = DocumentTimeline { DocumentTimeline -> JSVal
unDocumentTimeline :: JSVal }

instance PToJSVal DocumentTimeline where
  pToJSVal :: DocumentTimeline -> JSVal
pToJSVal = DocumentTimeline -> JSVal
unDocumentTimeline
  {-# INLINE pToJSVal #-}

instance PFromJSVal DocumentTimeline where
  pFromJSVal :: JSVal -> DocumentTimeline
pFromJSVal = JSVal -> DocumentTimeline
DocumentTimeline
  {-# INLINE pFromJSVal #-}

instance ToJSVal DocumentTimeline where
  toJSVal :: DocumentTimeline -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DocumentTimeline -> JSVal) -> DocumentTimeline -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocumentTimeline -> JSVal
unDocumentTimeline
  {-# INLINE toJSVal #-}

instance FromJSVal DocumentTimeline where
  fromJSVal :: JSVal -> JSM (Maybe DocumentTimeline)
fromJSVal JSVal
v = (JSVal -> DocumentTimeline)
-> Maybe JSVal -> Maybe DocumentTimeline
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DocumentTimeline
DocumentTimeline (Maybe JSVal -> Maybe DocumentTimeline)
-> JSM (Maybe JSVal) -> JSM (Maybe DocumentTimeline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DocumentTimeline
fromJSValUnchecked = DocumentTimeline -> JSM DocumentTimeline
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DocumentTimeline -> JSM DocumentTimeline)
-> (JSVal -> DocumentTimeline) -> JSVal -> JSM DocumentTimeline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DocumentTimeline
DocumentTimeline
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DocumentTimeline where
  makeObject :: DocumentTimeline -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DocumentTimeline -> JSVal) -> DocumentTimeline -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocumentTimeline -> JSVal
unDocumentTimeline

instance IsAnimationTimeline DocumentTimeline
instance IsGObject DocumentTimeline where
  typeGType :: DocumentTimeline -> JSM GType
typeGType DocumentTimeline
_ = JSM GType
gTypeDocumentTimeline
  {-# INLINE typeGType #-}

noDocumentTimeline :: Maybe DocumentTimeline
noDocumentTimeline :: Maybe DocumentTimeline
noDocumentTimeline = Maybe DocumentTimeline
forall a. Maybe a
Nothing
{-# INLINE noDocumentTimeline #-}

gTypeDocumentTimeline :: JSM GType
gTypeDocumentTimeline :: JSM GType
gTypeDocumentTimeline = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DocumentTimeline"

-- | Functions for this inteface are in "JSDOM.DocumentType".
-- Base interface functions are in:
--
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.ChildNode"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DocumentType Mozilla DocumentType documentation>
newtype DocumentType = DocumentType { DocumentType -> JSVal
unDocumentType :: JSVal }

instance PToJSVal DocumentType where
  pToJSVal :: DocumentType -> JSVal
pToJSVal = DocumentType -> JSVal
unDocumentType
  {-# INLINE pToJSVal #-}

instance PFromJSVal DocumentType where
  pFromJSVal :: JSVal -> DocumentType
pFromJSVal = JSVal -> DocumentType
DocumentType
  {-# INLINE pFromJSVal #-}

instance ToJSVal DocumentType where
  toJSVal :: DocumentType -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DocumentType -> JSVal) -> DocumentType -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocumentType -> JSVal
unDocumentType
  {-# INLINE toJSVal #-}

instance FromJSVal DocumentType where
  fromJSVal :: JSVal -> JSM (Maybe DocumentType)
fromJSVal JSVal
v = (JSVal -> DocumentType) -> Maybe JSVal -> Maybe DocumentType
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DocumentType
DocumentType (Maybe JSVal -> Maybe DocumentType)
-> JSM (Maybe JSVal) -> JSM (Maybe DocumentType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DocumentType
fromJSValUnchecked = DocumentType -> JSM DocumentType
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DocumentType -> JSM DocumentType)
-> (JSVal -> DocumentType) -> JSVal -> JSM DocumentType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DocumentType
DocumentType
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DocumentType where
  makeObject :: DocumentType -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DocumentType -> JSVal) -> DocumentType -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocumentType -> JSVal
unDocumentType

instance IsNode DocumentType
instance IsEventTarget DocumentType
instance IsChildNode DocumentType
instance IsGObject DocumentType where
  typeGType :: DocumentType -> JSM GType
typeGType DocumentType
_ = JSM GType
gTypeDocumentType
  {-# INLINE typeGType #-}

noDocumentType :: Maybe DocumentType
noDocumentType :: Maybe DocumentType
noDocumentType = Maybe DocumentType
forall a. Maybe a
Nothing
{-# INLINE noDocumentType #-}

gTypeDocumentType :: JSM GType
gTypeDocumentType :: JSM GType
gTypeDocumentType = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DocumentType"

-- | Functions for this inteface are in "JSDOM.DoubleRange".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DoubleRange Mozilla DoubleRange documentation>
newtype DoubleRange = DoubleRange { DoubleRange -> JSVal
unDoubleRange :: JSVal }

instance PToJSVal DoubleRange where
  pToJSVal :: DoubleRange -> JSVal
pToJSVal = DoubleRange -> JSVal
unDoubleRange
  {-# INLINE pToJSVal #-}

instance PFromJSVal DoubleRange where
  pFromJSVal :: JSVal -> DoubleRange
pFromJSVal = JSVal -> DoubleRange
DoubleRange
  {-# INLINE pFromJSVal #-}

instance ToJSVal DoubleRange where
  toJSVal :: DoubleRange -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DoubleRange -> JSVal) -> DoubleRange -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DoubleRange -> JSVal
unDoubleRange
  {-# INLINE toJSVal #-}

instance FromJSVal DoubleRange where
  fromJSVal :: JSVal -> JSM (Maybe DoubleRange)
fromJSVal JSVal
v = (JSVal -> DoubleRange) -> Maybe JSVal -> Maybe DoubleRange
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DoubleRange
DoubleRange (Maybe JSVal -> Maybe DoubleRange)
-> JSM (Maybe JSVal) -> JSM (Maybe DoubleRange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DoubleRange
fromJSValUnchecked = DoubleRange -> JSM DoubleRange
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DoubleRange -> JSM DoubleRange)
-> (JSVal -> DoubleRange) -> JSVal -> JSM DoubleRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DoubleRange
DoubleRange
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DoubleRange where
  makeObject :: DoubleRange -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DoubleRange -> JSVal) -> DoubleRange -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DoubleRange -> JSVal
unDoubleRange

class (IsGObject o) => IsDoubleRange o
toDoubleRange :: IsDoubleRange o => o -> DoubleRange
toDoubleRange :: forall o. IsDoubleRange o => o -> DoubleRange
toDoubleRange = JSVal -> DoubleRange
DoubleRange (JSVal -> DoubleRange) -> (o -> JSVal) -> o -> DoubleRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsDoubleRange DoubleRange
instance IsGObject DoubleRange where
  typeGType :: DoubleRange -> JSM GType
typeGType DoubleRange
_ = JSM GType
gTypeDoubleRange
  {-# INLINE typeGType #-}

noDoubleRange :: Maybe DoubleRange
noDoubleRange :: Maybe DoubleRange
noDoubleRange = Maybe DoubleRange
forall a. Maybe a
Nothing
{-# INLINE noDoubleRange #-}

gTypeDoubleRange :: JSM GType
gTypeDoubleRange :: JSM GType
gTypeDoubleRange = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DoubleRange"

-- | Functions for this inteface are in "JSDOM.DynamicsCompressorNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/DynamicsCompressorNode Mozilla DynamicsCompressorNode documentation>
newtype DynamicsCompressorNode = DynamicsCompressorNode { DynamicsCompressorNode -> JSVal
unDynamicsCompressorNode :: JSVal }

instance PToJSVal DynamicsCompressorNode where
  pToJSVal :: DynamicsCompressorNode -> JSVal
pToJSVal = DynamicsCompressorNode -> JSVal
unDynamicsCompressorNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal DynamicsCompressorNode where
  pFromJSVal :: JSVal -> DynamicsCompressorNode
pFromJSVal = JSVal -> DynamicsCompressorNode
DynamicsCompressorNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal DynamicsCompressorNode where
  toJSVal :: DynamicsCompressorNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (DynamicsCompressorNode -> JSVal)
-> DynamicsCompressorNode
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DynamicsCompressorNode -> JSVal
unDynamicsCompressorNode
  {-# INLINE toJSVal #-}

instance FromJSVal DynamicsCompressorNode where
  fromJSVal :: JSVal -> JSM (Maybe DynamicsCompressorNode)
fromJSVal JSVal
v = (JSVal -> DynamicsCompressorNode)
-> Maybe JSVal -> Maybe DynamicsCompressorNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> DynamicsCompressorNode
DynamicsCompressorNode (Maybe JSVal -> Maybe DynamicsCompressorNode)
-> JSM (Maybe JSVal) -> JSM (Maybe DynamicsCompressorNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM DynamicsCompressorNode
fromJSValUnchecked = DynamicsCompressorNode -> JSM DynamicsCompressorNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (DynamicsCompressorNode -> JSM DynamicsCompressorNode)
-> (JSVal -> DynamicsCompressorNode)
-> JSVal
-> JSM DynamicsCompressorNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> DynamicsCompressorNode
DynamicsCompressorNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject DynamicsCompressorNode where
  makeObject :: DynamicsCompressorNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (DynamicsCompressorNode -> JSVal)
-> DynamicsCompressorNode
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DynamicsCompressorNode -> JSVal
unDynamicsCompressorNode

instance IsAudioNode DynamicsCompressorNode
instance IsEventTarget DynamicsCompressorNode
instance IsGObject DynamicsCompressorNode where
  typeGType :: DynamicsCompressorNode -> JSM GType
typeGType DynamicsCompressorNode
_ = JSM GType
gTypeDynamicsCompressorNode
  {-# INLINE typeGType #-}

noDynamicsCompressorNode :: Maybe DynamicsCompressorNode
noDynamicsCompressorNode :: Maybe DynamicsCompressorNode
noDynamicsCompressorNode = Maybe DynamicsCompressorNode
forall a. Maybe a
Nothing
{-# INLINE noDynamicsCompressorNode #-}

gTypeDynamicsCompressorNode :: JSM GType
gTypeDynamicsCompressorNode :: JSM GType
gTypeDynamicsCompressorNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"DynamicsCompressorNode"

-- | Functions for this inteface are in "JSDOM.EXTBlendMinMax".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EXTBlendMinMax Mozilla EXTBlendMinMax documentation>
newtype EXTBlendMinMax = EXTBlendMinMax { EXTBlendMinMax -> JSVal
unEXTBlendMinMax :: JSVal }

instance PToJSVal EXTBlendMinMax where
  pToJSVal :: EXTBlendMinMax -> JSVal
pToJSVal = EXTBlendMinMax -> JSVal
unEXTBlendMinMax
  {-# INLINE pToJSVal #-}

instance PFromJSVal EXTBlendMinMax where
  pFromJSVal :: JSVal -> EXTBlendMinMax
pFromJSVal = JSVal -> EXTBlendMinMax
EXTBlendMinMax
  {-# INLINE pFromJSVal #-}

instance ToJSVal EXTBlendMinMax where
  toJSVal :: EXTBlendMinMax -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EXTBlendMinMax -> JSVal) -> EXTBlendMinMax -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EXTBlendMinMax -> JSVal
unEXTBlendMinMax
  {-# INLINE toJSVal #-}

instance FromJSVal EXTBlendMinMax where
  fromJSVal :: JSVal -> JSM (Maybe EXTBlendMinMax)
fromJSVal JSVal
v = (JSVal -> EXTBlendMinMax) -> Maybe JSVal -> Maybe EXTBlendMinMax
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EXTBlendMinMax
EXTBlendMinMax (Maybe JSVal -> Maybe EXTBlendMinMax)
-> JSM (Maybe JSVal) -> JSM (Maybe EXTBlendMinMax)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EXTBlendMinMax
fromJSValUnchecked = EXTBlendMinMax -> JSM EXTBlendMinMax
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EXTBlendMinMax -> JSM EXTBlendMinMax)
-> (JSVal -> EXTBlendMinMax) -> JSVal -> JSM EXTBlendMinMax
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EXTBlendMinMax
EXTBlendMinMax
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EXTBlendMinMax where
  makeObject :: EXTBlendMinMax -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EXTBlendMinMax -> JSVal) -> EXTBlendMinMax -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EXTBlendMinMax -> JSVal
unEXTBlendMinMax

instance IsGObject EXTBlendMinMax where
  typeGType :: EXTBlendMinMax -> JSM GType
typeGType EXTBlendMinMax
_ = JSM GType
gTypeEXTBlendMinMax
  {-# INLINE typeGType #-}

noEXTBlendMinMax :: Maybe EXTBlendMinMax
noEXTBlendMinMax :: Maybe EXTBlendMinMax
noEXTBlendMinMax = Maybe EXTBlendMinMax
forall a. Maybe a
Nothing
{-# INLINE noEXTBlendMinMax #-}

gTypeEXTBlendMinMax :: JSM GType
gTypeEXTBlendMinMax :: JSM GType
gTypeEXTBlendMinMax = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EXTBlendMinMax"

-- | Functions for this inteface are in "JSDOM.EXTFragDepth".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EXTFragDepth Mozilla EXTFragDepth documentation>
newtype EXTFragDepth = EXTFragDepth { EXTFragDepth -> JSVal
unEXTFragDepth :: JSVal }

instance PToJSVal EXTFragDepth where
  pToJSVal :: EXTFragDepth -> JSVal
pToJSVal = EXTFragDepth -> JSVal
unEXTFragDepth
  {-# INLINE pToJSVal #-}

instance PFromJSVal EXTFragDepth where
  pFromJSVal :: JSVal -> EXTFragDepth
pFromJSVal = JSVal -> EXTFragDepth
EXTFragDepth
  {-# INLINE pFromJSVal #-}

instance ToJSVal EXTFragDepth where
  toJSVal :: EXTFragDepth -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EXTFragDepth -> JSVal) -> EXTFragDepth -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EXTFragDepth -> JSVal
unEXTFragDepth
  {-# INLINE toJSVal #-}

instance FromJSVal EXTFragDepth where
  fromJSVal :: JSVal -> JSM (Maybe EXTFragDepth)
fromJSVal JSVal
v = (JSVal -> EXTFragDepth) -> Maybe JSVal -> Maybe EXTFragDepth
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EXTFragDepth
EXTFragDepth (Maybe JSVal -> Maybe EXTFragDepth)
-> JSM (Maybe JSVal) -> JSM (Maybe EXTFragDepth)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EXTFragDepth
fromJSValUnchecked = EXTFragDepth -> JSM EXTFragDepth
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EXTFragDepth -> JSM EXTFragDepth)
-> (JSVal -> EXTFragDepth) -> JSVal -> JSM EXTFragDepth
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EXTFragDepth
EXTFragDepth
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EXTFragDepth where
  makeObject :: EXTFragDepth -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EXTFragDepth -> JSVal) -> EXTFragDepth -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EXTFragDepth -> JSVal
unEXTFragDepth

instance IsGObject EXTFragDepth where
  typeGType :: EXTFragDepth -> JSM GType
typeGType EXTFragDepth
_ = JSM GType
gTypeEXTFragDepth
  {-# INLINE typeGType #-}

noEXTFragDepth :: Maybe EXTFragDepth
noEXTFragDepth :: Maybe EXTFragDepth
noEXTFragDepth = Maybe EXTFragDepth
forall a. Maybe a
Nothing
{-# INLINE noEXTFragDepth #-}

gTypeEXTFragDepth :: JSM GType
gTypeEXTFragDepth :: JSM GType
gTypeEXTFragDepth = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EXTFragDepth"

-- | Functions for this inteface are in "JSDOM.EXTShaderTextureLOD".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EXTShaderTextureLOD Mozilla EXTShaderTextureLOD documentation>
newtype EXTShaderTextureLOD = EXTShaderTextureLOD { EXTShaderTextureLOD -> JSVal
unEXTShaderTextureLOD :: JSVal }

instance PToJSVal EXTShaderTextureLOD where
  pToJSVal :: EXTShaderTextureLOD -> JSVal
pToJSVal = EXTShaderTextureLOD -> JSVal
unEXTShaderTextureLOD
  {-# INLINE pToJSVal #-}

instance PFromJSVal EXTShaderTextureLOD where
  pFromJSVal :: JSVal -> EXTShaderTextureLOD
pFromJSVal = JSVal -> EXTShaderTextureLOD
EXTShaderTextureLOD
  {-# INLINE pFromJSVal #-}

instance ToJSVal EXTShaderTextureLOD where
  toJSVal :: EXTShaderTextureLOD -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EXTShaderTextureLOD -> JSVal)
-> EXTShaderTextureLOD
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EXTShaderTextureLOD -> JSVal
unEXTShaderTextureLOD
  {-# INLINE toJSVal #-}

instance FromJSVal EXTShaderTextureLOD where
  fromJSVal :: JSVal -> JSM (Maybe EXTShaderTextureLOD)
fromJSVal JSVal
v = (JSVal -> EXTShaderTextureLOD)
-> Maybe JSVal -> Maybe EXTShaderTextureLOD
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EXTShaderTextureLOD
EXTShaderTextureLOD (Maybe JSVal -> Maybe EXTShaderTextureLOD)
-> JSM (Maybe JSVal) -> JSM (Maybe EXTShaderTextureLOD)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EXTShaderTextureLOD
fromJSValUnchecked = EXTShaderTextureLOD -> JSM EXTShaderTextureLOD
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EXTShaderTextureLOD -> JSM EXTShaderTextureLOD)
-> (JSVal -> EXTShaderTextureLOD)
-> JSVal
-> JSM EXTShaderTextureLOD
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EXTShaderTextureLOD
EXTShaderTextureLOD
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EXTShaderTextureLOD where
  makeObject :: EXTShaderTextureLOD -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EXTShaderTextureLOD -> JSVal)
-> EXTShaderTextureLOD
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EXTShaderTextureLOD -> JSVal
unEXTShaderTextureLOD

instance IsGObject EXTShaderTextureLOD where
  typeGType :: EXTShaderTextureLOD -> JSM GType
typeGType EXTShaderTextureLOD
_ = JSM GType
gTypeEXTShaderTextureLOD
  {-# INLINE typeGType #-}

noEXTShaderTextureLOD :: Maybe EXTShaderTextureLOD
noEXTShaderTextureLOD :: Maybe EXTShaderTextureLOD
noEXTShaderTextureLOD = Maybe EXTShaderTextureLOD
forall a. Maybe a
Nothing
{-# INLINE noEXTShaderTextureLOD #-}

gTypeEXTShaderTextureLOD :: JSM GType
gTypeEXTShaderTextureLOD :: JSM GType
gTypeEXTShaderTextureLOD = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EXTShaderTextureLOD"

-- | Functions for this inteface are in "JSDOM.EXTTextureFilterAnisotropic".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EXTTextureFilterAnisotropic Mozilla EXTTextureFilterAnisotropic documentation>
newtype EXTTextureFilterAnisotropic = EXTTextureFilterAnisotropic { EXTTextureFilterAnisotropic -> JSVal
unEXTTextureFilterAnisotropic :: JSVal }

instance PToJSVal EXTTextureFilterAnisotropic where
  pToJSVal :: EXTTextureFilterAnisotropic -> JSVal
pToJSVal = EXTTextureFilterAnisotropic -> JSVal
unEXTTextureFilterAnisotropic
  {-# INLINE pToJSVal #-}

instance PFromJSVal EXTTextureFilterAnisotropic where
  pFromJSVal :: JSVal -> EXTTextureFilterAnisotropic
pFromJSVal = JSVal -> EXTTextureFilterAnisotropic
EXTTextureFilterAnisotropic
  {-# INLINE pFromJSVal #-}

instance ToJSVal EXTTextureFilterAnisotropic where
  toJSVal :: EXTTextureFilterAnisotropic -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EXTTextureFilterAnisotropic -> JSVal)
-> EXTTextureFilterAnisotropic
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EXTTextureFilterAnisotropic -> JSVal
unEXTTextureFilterAnisotropic
  {-# INLINE toJSVal #-}

instance FromJSVal EXTTextureFilterAnisotropic where
  fromJSVal :: JSVal -> JSM (Maybe EXTTextureFilterAnisotropic)
fromJSVal JSVal
v = (JSVal -> EXTTextureFilterAnisotropic)
-> Maybe JSVal -> Maybe EXTTextureFilterAnisotropic
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EXTTextureFilterAnisotropic
EXTTextureFilterAnisotropic (Maybe JSVal -> Maybe EXTTextureFilterAnisotropic)
-> JSM (Maybe JSVal) -> JSM (Maybe EXTTextureFilterAnisotropic)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EXTTextureFilterAnisotropic
fromJSValUnchecked = EXTTextureFilterAnisotropic -> JSM EXTTextureFilterAnisotropic
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EXTTextureFilterAnisotropic -> JSM EXTTextureFilterAnisotropic)
-> (JSVal -> EXTTextureFilterAnisotropic)
-> JSVal
-> JSM EXTTextureFilterAnisotropic
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EXTTextureFilterAnisotropic
EXTTextureFilterAnisotropic
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EXTTextureFilterAnisotropic where
  makeObject :: EXTTextureFilterAnisotropic -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EXTTextureFilterAnisotropic -> JSVal)
-> EXTTextureFilterAnisotropic
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EXTTextureFilterAnisotropic -> JSVal
unEXTTextureFilterAnisotropic

instance IsGObject EXTTextureFilterAnisotropic where
  typeGType :: EXTTextureFilterAnisotropic -> JSM GType
typeGType EXTTextureFilterAnisotropic
_ = JSM GType
gTypeEXTTextureFilterAnisotropic
  {-# INLINE typeGType #-}

noEXTTextureFilterAnisotropic :: Maybe EXTTextureFilterAnisotropic
noEXTTextureFilterAnisotropic :: Maybe EXTTextureFilterAnisotropic
noEXTTextureFilterAnisotropic = Maybe EXTTextureFilterAnisotropic
forall a. Maybe a
Nothing
{-# INLINE noEXTTextureFilterAnisotropic #-}

gTypeEXTTextureFilterAnisotropic :: JSM GType
gTypeEXTTextureFilterAnisotropic :: JSM GType
gTypeEXTTextureFilterAnisotropic = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EXTTextureFilterAnisotropic"

-- | Functions for this inteface are in "JSDOM.EXTsRGB".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EXTsRGB Mozilla EXTsRGB documentation>
newtype EXTsRGB = EXTsRGB { EXTsRGB -> JSVal
unEXTsRGB :: JSVal }

instance PToJSVal EXTsRGB where
  pToJSVal :: EXTsRGB -> JSVal
pToJSVal = EXTsRGB -> JSVal
unEXTsRGB
  {-# INLINE pToJSVal #-}

instance PFromJSVal EXTsRGB where
  pFromJSVal :: JSVal -> EXTsRGB
pFromJSVal = JSVal -> EXTsRGB
EXTsRGB
  {-# INLINE pFromJSVal #-}

instance ToJSVal EXTsRGB where
  toJSVal :: EXTsRGB -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (EXTsRGB -> JSVal) -> EXTsRGB -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EXTsRGB -> JSVal
unEXTsRGB
  {-# INLINE toJSVal #-}

instance FromJSVal EXTsRGB where
  fromJSVal :: JSVal -> JSM (Maybe EXTsRGB)
fromJSVal JSVal
v = (JSVal -> EXTsRGB) -> Maybe JSVal -> Maybe EXTsRGB
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EXTsRGB
EXTsRGB (Maybe JSVal -> Maybe EXTsRGB)
-> JSM (Maybe JSVal) -> JSM (Maybe EXTsRGB)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EXTsRGB
fromJSValUnchecked = EXTsRGB -> JSM EXTsRGB
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EXTsRGB -> JSM EXTsRGB)
-> (JSVal -> EXTsRGB) -> JSVal -> JSM EXTsRGB
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EXTsRGB
EXTsRGB
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EXTsRGB where
  makeObject :: EXTsRGB -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EXTsRGB -> JSVal) -> EXTsRGB -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EXTsRGB -> JSVal
unEXTsRGB

instance IsGObject EXTsRGB where
  typeGType :: EXTsRGB -> JSM GType
typeGType EXTsRGB
_ = JSM GType
gTypeEXTsRGB
  {-# INLINE typeGType #-}

noEXTsRGB :: Maybe EXTsRGB
noEXTsRGB :: Maybe EXTsRGB
noEXTsRGB = Maybe EXTsRGB
forall a. Maybe a
Nothing
{-# INLINE noEXTsRGB #-}

gTypeEXTsRGB :: JSM GType
gTypeEXTsRGB :: JSM GType
gTypeEXTsRGB = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EXTsRGB"

-- | Functions for this inteface are in "JSDOM.EcKeyParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EcKeyParams Mozilla EcKeyParams documentation>
newtype EcKeyParams = EcKeyParams { EcKeyParams -> JSVal
unEcKeyParams :: JSVal }

instance PToJSVal EcKeyParams where
  pToJSVal :: EcKeyParams -> JSVal
pToJSVal = EcKeyParams -> JSVal
unEcKeyParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal EcKeyParams where
  pFromJSVal :: JSVal -> EcKeyParams
pFromJSVal = JSVal -> EcKeyParams
EcKeyParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal EcKeyParams where
  toJSVal :: EcKeyParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EcKeyParams -> JSVal) -> EcKeyParams -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EcKeyParams -> JSVal
unEcKeyParams
  {-# INLINE toJSVal #-}

instance FromJSVal EcKeyParams where
  fromJSVal :: JSVal -> JSM (Maybe EcKeyParams)
fromJSVal JSVal
v = (JSVal -> EcKeyParams) -> Maybe JSVal -> Maybe EcKeyParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EcKeyParams
EcKeyParams (Maybe JSVal -> Maybe EcKeyParams)
-> JSM (Maybe JSVal) -> JSM (Maybe EcKeyParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EcKeyParams
fromJSValUnchecked = EcKeyParams -> JSM EcKeyParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EcKeyParams -> JSM EcKeyParams)
-> (JSVal -> EcKeyParams) -> JSVal -> JSM EcKeyParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EcKeyParams
EcKeyParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EcKeyParams where
  makeObject :: EcKeyParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EcKeyParams -> JSVal) -> EcKeyParams -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EcKeyParams -> JSVal
unEcKeyParams

instance IsCryptoAlgorithmParameters EcKeyParams
instance IsGObject EcKeyParams where
  typeGType :: EcKeyParams -> JSM GType
typeGType EcKeyParams
_ = JSM GType
gTypeEcKeyParams
  {-# INLINE typeGType #-}

noEcKeyParams :: Maybe EcKeyParams
noEcKeyParams :: Maybe EcKeyParams
noEcKeyParams = Maybe EcKeyParams
forall a. Maybe a
Nothing
{-# INLINE noEcKeyParams #-}

gTypeEcKeyParams :: JSM GType
gTypeEcKeyParams :: JSM GType
gTypeEcKeyParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EcKeyParams"

-- | Functions for this inteface are in "JSDOM.EcdhKeyDeriveParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EcdhKeyDeriveParams Mozilla EcdhKeyDeriveParams documentation>
newtype EcdhKeyDeriveParams = EcdhKeyDeriveParams { EcdhKeyDeriveParams -> JSVal
unEcdhKeyDeriveParams :: JSVal }

instance PToJSVal EcdhKeyDeriveParams where
  pToJSVal :: EcdhKeyDeriveParams -> JSVal
pToJSVal = EcdhKeyDeriveParams -> JSVal
unEcdhKeyDeriveParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal EcdhKeyDeriveParams where
  pFromJSVal :: JSVal -> EcdhKeyDeriveParams
pFromJSVal = JSVal -> EcdhKeyDeriveParams
EcdhKeyDeriveParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal EcdhKeyDeriveParams where
  toJSVal :: EcdhKeyDeriveParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EcdhKeyDeriveParams -> JSVal)
-> EcdhKeyDeriveParams
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EcdhKeyDeriveParams -> JSVal
unEcdhKeyDeriveParams
  {-# INLINE toJSVal #-}

instance FromJSVal EcdhKeyDeriveParams where
  fromJSVal :: JSVal -> JSM (Maybe EcdhKeyDeriveParams)
fromJSVal JSVal
v = (JSVal -> EcdhKeyDeriveParams)
-> Maybe JSVal -> Maybe EcdhKeyDeriveParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EcdhKeyDeriveParams
EcdhKeyDeriveParams (Maybe JSVal -> Maybe EcdhKeyDeriveParams)
-> JSM (Maybe JSVal) -> JSM (Maybe EcdhKeyDeriveParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EcdhKeyDeriveParams
fromJSValUnchecked = EcdhKeyDeriveParams -> JSM EcdhKeyDeriveParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EcdhKeyDeriveParams -> JSM EcdhKeyDeriveParams)
-> (JSVal -> EcdhKeyDeriveParams)
-> JSVal
-> JSM EcdhKeyDeriveParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EcdhKeyDeriveParams
EcdhKeyDeriveParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EcdhKeyDeriveParams where
  makeObject :: EcdhKeyDeriveParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EcdhKeyDeriveParams -> JSVal)
-> EcdhKeyDeriveParams
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EcdhKeyDeriveParams -> JSVal
unEcdhKeyDeriveParams

instance IsCryptoAlgorithmParameters EcdhKeyDeriveParams
instance IsGObject EcdhKeyDeriveParams where
  typeGType :: EcdhKeyDeriveParams -> JSM GType
typeGType EcdhKeyDeriveParams
_ = JSM GType
gTypeEcdhKeyDeriveParams
  {-# INLINE typeGType #-}

noEcdhKeyDeriveParams :: Maybe EcdhKeyDeriveParams
noEcdhKeyDeriveParams :: Maybe EcdhKeyDeriveParams
noEcdhKeyDeriveParams = Maybe EcdhKeyDeriveParams
forall a. Maybe a
Nothing
{-# INLINE noEcdhKeyDeriveParams #-}

gTypeEcdhKeyDeriveParams :: JSM GType
gTypeEcdhKeyDeriveParams :: JSM GType
gTypeEcdhKeyDeriveParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EcdhKeyDeriveParams"

-- | Functions for this inteface are in "JSDOM.EcdsaParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EcdsaParams Mozilla EcdsaParams documentation>
newtype EcdsaParams = EcdsaParams { EcdsaParams -> JSVal
unEcdsaParams :: JSVal }

instance PToJSVal EcdsaParams where
  pToJSVal :: EcdsaParams -> JSVal
pToJSVal = EcdsaParams -> JSVal
unEcdsaParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal EcdsaParams where
  pFromJSVal :: JSVal -> EcdsaParams
pFromJSVal = JSVal -> EcdsaParams
EcdsaParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal EcdsaParams where
  toJSVal :: EcdsaParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EcdsaParams -> JSVal) -> EcdsaParams -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EcdsaParams -> JSVal
unEcdsaParams
  {-# INLINE toJSVal #-}

instance FromJSVal EcdsaParams where
  fromJSVal :: JSVal -> JSM (Maybe EcdsaParams)
fromJSVal JSVal
v = (JSVal -> EcdsaParams) -> Maybe JSVal -> Maybe EcdsaParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EcdsaParams
EcdsaParams (Maybe JSVal -> Maybe EcdsaParams)
-> JSM (Maybe JSVal) -> JSM (Maybe EcdsaParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EcdsaParams
fromJSValUnchecked = EcdsaParams -> JSM EcdsaParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EcdsaParams -> JSM EcdsaParams)
-> (JSVal -> EcdsaParams) -> JSVal -> JSM EcdsaParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EcdsaParams
EcdsaParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EcdsaParams where
  makeObject :: EcdsaParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EcdsaParams -> JSVal) -> EcdsaParams -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EcdsaParams -> JSVal
unEcdsaParams

instance IsCryptoAlgorithmParameters EcdsaParams
instance IsGObject EcdsaParams where
  typeGType :: EcdsaParams -> JSM GType
typeGType EcdsaParams
_ = JSM GType
gTypeEcdsaParams
  {-# INLINE typeGType #-}

noEcdsaParams :: Maybe EcdsaParams
noEcdsaParams :: Maybe EcdsaParams
noEcdsaParams = Maybe EcdsaParams
forall a. Maybe a
Nothing
{-# INLINE noEcdsaParams #-}

gTypeEcdsaParams :: JSM GType
gTypeEcdsaParams :: JSM GType
gTypeEcdsaParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EcdsaParams"

-- | Functions for this inteface are in "JSDOM.Element".
-- Base interface functions are in:
--
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Element Mozilla Element documentation>
newtype Element = Element { Element -> JSVal
unElement :: JSVal }

instance PToJSVal Element where
  pToJSVal :: Element -> JSVal
pToJSVal = Element -> JSVal
unElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal Element where
  pFromJSVal :: JSVal -> Element
pFromJSVal = JSVal -> Element
Element
  {-# INLINE pFromJSVal #-}

instance ToJSVal Element where
  toJSVal :: Element -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Element -> JSVal) -> Element -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> JSVal
unElement
  {-# INLINE toJSVal #-}

instance FromJSVal Element where
  fromJSVal :: JSVal -> JSM (Maybe Element)
fromJSVal JSVal
v = (JSVal -> Element) -> Maybe JSVal -> Maybe Element
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Element
Element (Maybe JSVal -> Maybe Element)
-> JSM (Maybe JSVal) -> JSM (Maybe Element)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Element
fromJSValUnchecked = Element -> JSM Element
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> JSM Element)
-> (JSVal -> Element) -> JSVal -> JSM Element
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Element
Element
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Element where
  makeObject :: Element -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Element -> JSVal) -> Element -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> JSVal
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 :: forall o. IsElement o => o -> Element
toElement = JSVal -> Element
Element (JSVal -> Element) -> (o -> JSVal) -> o -> Element
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: Element -> JSM GType
typeGType Element
_ = JSM GType
gTypeElement
  {-# INLINE typeGType #-}

noElement :: Maybe Element
noElement :: Maybe Element
noElement = Maybe Element
forall a. Maybe a
Nothing
{-# INLINE noElement #-}

gTypeElement :: JSM GType
gTypeElement :: JSM GType
gTypeElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Element"

-- | Functions for this inteface are in "JSDOM.ElementCSSInlineStyle".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ElementCSSInlineStyle Mozilla ElementCSSInlineStyle documentation>
newtype ElementCSSInlineStyle = ElementCSSInlineStyle { ElementCSSInlineStyle -> JSVal
unElementCSSInlineStyle :: JSVal }

instance PToJSVal ElementCSSInlineStyle where
  pToJSVal :: ElementCSSInlineStyle -> JSVal
pToJSVal = ElementCSSInlineStyle -> JSVal
unElementCSSInlineStyle
  {-# INLINE pToJSVal #-}

instance PFromJSVal ElementCSSInlineStyle where
  pFromJSVal :: JSVal -> ElementCSSInlineStyle
pFromJSVal = JSVal -> ElementCSSInlineStyle
ElementCSSInlineStyle
  {-# INLINE pFromJSVal #-}

instance ToJSVal ElementCSSInlineStyle where
  toJSVal :: ElementCSSInlineStyle -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ElementCSSInlineStyle -> JSVal)
-> ElementCSSInlineStyle
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElementCSSInlineStyle -> JSVal
unElementCSSInlineStyle
  {-# INLINE toJSVal #-}

instance FromJSVal ElementCSSInlineStyle where
  fromJSVal :: JSVal -> JSM (Maybe ElementCSSInlineStyle)
fromJSVal JSVal
v = (JSVal -> ElementCSSInlineStyle)
-> Maybe JSVal -> Maybe ElementCSSInlineStyle
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ElementCSSInlineStyle
ElementCSSInlineStyle (Maybe JSVal -> Maybe ElementCSSInlineStyle)
-> JSM (Maybe JSVal) -> JSM (Maybe ElementCSSInlineStyle)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ElementCSSInlineStyle
fromJSValUnchecked = ElementCSSInlineStyle -> JSM ElementCSSInlineStyle
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ElementCSSInlineStyle -> JSM ElementCSSInlineStyle)
-> (JSVal -> ElementCSSInlineStyle)
-> JSVal
-> JSM ElementCSSInlineStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ElementCSSInlineStyle
ElementCSSInlineStyle
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ElementCSSInlineStyle where
  makeObject :: ElementCSSInlineStyle -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ElementCSSInlineStyle -> JSVal)
-> ElementCSSInlineStyle
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElementCSSInlineStyle -> JSVal
unElementCSSInlineStyle

class (IsGObject o) => IsElementCSSInlineStyle o
toElementCSSInlineStyle :: IsElementCSSInlineStyle o => o -> ElementCSSInlineStyle
toElementCSSInlineStyle :: forall o. IsElementCSSInlineStyle o => o -> ElementCSSInlineStyle
toElementCSSInlineStyle = JSVal -> ElementCSSInlineStyle
ElementCSSInlineStyle (JSVal -> ElementCSSInlineStyle)
-> (o -> JSVal) -> o -> ElementCSSInlineStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsElementCSSInlineStyle ElementCSSInlineStyle
instance IsGObject ElementCSSInlineStyle where
  typeGType :: ElementCSSInlineStyle -> JSM GType
typeGType ElementCSSInlineStyle
_ = JSM GType
gTypeElementCSSInlineStyle
  {-# INLINE typeGType #-}

noElementCSSInlineStyle :: Maybe ElementCSSInlineStyle
noElementCSSInlineStyle :: Maybe ElementCSSInlineStyle
noElementCSSInlineStyle = Maybe ElementCSSInlineStyle
forall a. Maybe a
Nothing
{-# INLINE noElementCSSInlineStyle #-}

gTypeElementCSSInlineStyle :: JSM GType
gTypeElementCSSInlineStyle :: JSM GType
gTypeElementCSSInlineStyle = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ElementCSSInlineStyle"

-- | Functions for this inteface are in "JSDOM.ErrorEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ErrorEvent Mozilla ErrorEvent documentation>
newtype ErrorEvent = ErrorEvent { ErrorEvent -> JSVal
unErrorEvent :: JSVal }

instance PToJSVal ErrorEvent where
  pToJSVal :: ErrorEvent -> JSVal
pToJSVal = ErrorEvent -> JSVal
unErrorEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal ErrorEvent where
  pFromJSVal :: JSVal -> ErrorEvent
pFromJSVal = JSVal -> ErrorEvent
ErrorEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal ErrorEvent where
  toJSVal :: ErrorEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ErrorEvent -> JSVal) -> ErrorEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorEvent -> JSVal
unErrorEvent
  {-# INLINE toJSVal #-}

instance FromJSVal ErrorEvent where
  fromJSVal :: JSVal -> JSM (Maybe ErrorEvent)
fromJSVal JSVal
v = (JSVal -> ErrorEvent) -> Maybe JSVal -> Maybe ErrorEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ErrorEvent
ErrorEvent (Maybe JSVal -> Maybe ErrorEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe ErrorEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ErrorEvent
fromJSValUnchecked = ErrorEvent -> JSM ErrorEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ErrorEvent -> JSM ErrorEvent)
-> (JSVal -> ErrorEvent) -> JSVal -> JSM ErrorEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ErrorEvent
ErrorEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ErrorEvent where
  makeObject :: ErrorEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ErrorEvent -> JSVal) -> ErrorEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorEvent -> JSVal
unErrorEvent

instance IsEvent ErrorEvent
instance IsGObject ErrorEvent where
  typeGType :: ErrorEvent -> JSM GType
typeGType ErrorEvent
_ = JSM GType
gTypeErrorEvent
  {-# INLINE typeGType #-}

noErrorEvent :: Maybe ErrorEvent
noErrorEvent :: Maybe ErrorEvent
noErrorEvent = Maybe ErrorEvent
forall a. Maybe a
Nothing
{-# INLINE noErrorEvent #-}

gTypeErrorEvent :: JSM GType
gTypeErrorEvent :: JSM GType
gTypeErrorEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ErrorEvent"

-- | Functions for this inteface are in "JSDOM.ErrorEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ErrorEventInit Mozilla ErrorEventInit documentation>
newtype ErrorEventInit = ErrorEventInit { ErrorEventInit -> JSVal
unErrorEventInit :: JSVal }

instance PToJSVal ErrorEventInit where
  pToJSVal :: ErrorEventInit -> JSVal
pToJSVal = ErrorEventInit -> JSVal
unErrorEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal ErrorEventInit where
  pFromJSVal :: JSVal -> ErrorEventInit
pFromJSVal = JSVal -> ErrorEventInit
ErrorEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal ErrorEventInit where
  toJSVal :: ErrorEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ErrorEventInit -> JSVal) -> ErrorEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorEventInit -> JSVal
unErrorEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal ErrorEventInit where
  fromJSVal :: JSVal -> JSM (Maybe ErrorEventInit)
fromJSVal JSVal
v = (JSVal -> ErrorEventInit) -> Maybe JSVal -> Maybe ErrorEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ErrorEventInit
ErrorEventInit (Maybe JSVal -> Maybe ErrorEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe ErrorEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ErrorEventInit
fromJSValUnchecked = ErrorEventInit -> JSM ErrorEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ErrorEventInit -> JSM ErrorEventInit)
-> (JSVal -> ErrorEventInit) -> JSVal -> JSM ErrorEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ErrorEventInit
ErrorEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ErrorEventInit where
  makeObject :: ErrorEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ErrorEventInit -> JSVal) -> ErrorEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorEventInit -> JSVal
unErrorEventInit

instance IsEventInit ErrorEventInit
instance IsGObject ErrorEventInit where
  typeGType :: ErrorEventInit -> JSM GType
typeGType ErrorEventInit
_ = JSM GType
gTypeErrorEventInit
  {-# INLINE typeGType #-}

noErrorEventInit :: Maybe ErrorEventInit
noErrorEventInit :: Maybe ErrorEventInit
noErrorEventInit = Maybe ErrorEventInit
forall a. Maybe a
Nothing
{-# INLINE noErrorEventInit #-}

gTypeErrorEventInit :: JSM GType
gTypeErrorEventInit :: JSM GType
gTypeErrorEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ErrorEventInit"

-- | Functions for this inteface are in "JSDOM.Event".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Event Mozilla Event documentation>
newtype Event = Event { Event -> JSVal
unEvent :: JSVal }

instance PToJSVal Event where
  pToJSVal :: Event -> JSVal
pToJSVal = Event -> JSVal
unEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal Event where
  pFromJSVal :: JSVal -> Event
pFromJSVal = JSVal -> Event
Event
  {-# INLINE pFromJSVal #-}

instance ToJSVal Event where
  toJSVal :: Event -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Event -> JSVal) -> Event -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event -> JSVal
unEvent
  {-# INLINE toJSVal #-}

instance FromJSVal Event where
  fromJSVal :: JSVal -> JSM (Maybe Event)
fromJSVal JSVal
v = (JSVal -> Event) -> Maybe JSVal -> Maybe Event
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Event
Event (Maybe JSVal -> Maybe Event)
-> JSM (Maybe JSVal) -> JSM (Maybe Event)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Event
fromJSValUnchecked = Event -> JSM Event
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> JSM Event) -> (JSVal -> Event) -> JSVal -> JSM Event
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Event
Event
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Event where
  makeObject :: Event -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Event -> JSVal) -> Event -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Event -> JSVal
unEvent

class (IsGObject o) => IsEvent o
toEvent :: IsEvent o => o -> Event
toEvent :: forall o. IsEvent o => o -> Event
toEvent = JSVal -> Event
Event (JSVal -> Event) -> (o -> JSVal) -> o -> Event
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsEvent Event
instance IsGObject Event where
  typeGType :: Event -> JSM GType
typeGType Event
_ = JSM GType
gTypeEvent
  {-# INLINE typeGType #-}

noEvent :: Maybe Event
noEvent :: Maybe Event
noEvent = Maybe Event
forall a. Maybe a
Nothing
{-# INLINE noEvent #-}

gTypeEvent :: JSM GType
gTypeEvent :: JSM GType
gTypeEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Event"

-- | Functions for this inteface are in "JSDOM.EventInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EventInit Mozilla EventInit documentation>
newtype EventInit = EventInit { EventInit -> JSVal
unEventInit :: JSVal }

instance PToJSVal EventInit where
  pToJSVal :: EventInit -> JSVal
pToJSVal = EventInit -> JSVal
unEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal EventInit where
  pFromJSVal :: JSVal -> EventInit
pFromJSVal = JSVal -> EventInit
EventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal EventInit where
  toJSVal :: EventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EventInit -> JSVal) -> EventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventInit -> JSVal
unEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal EventInit where
  fromJSVal :: JSVal -> JSM (Maybe EventInit)
fromJSVal JSVal
v = (JSVal -> EventInit) -> Maybe JSVal -> Maybe EventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EventInit
EventInit (Maybe JSVal -> Maybe EventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe EventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EventInit
fromJSValUnchecked = EventInit -> JSM EventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EventInit -> JSM EventInit)
-> (JSVal -> EventInit) -> JSVal -> JSM EventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EventInit
EventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EventInit where
  makeObject :: EventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EventInit -> JSVal) -> EventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventInit -> JSVal
unEventInit

class (IsGObject o) => IsEventInit o
toEventInit :: IsEventInit o => o -> EventInit
toEventInit :: forall o. IsEventInit o => o -> EventInit
toEventInit = JSVal -> EventInit
EventInit (JSVal -> EventInit) -> (o -> JSVal) -> o -> EventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsEventInit EventInit
instance IsGObject EventInit where
  typeGType :: EventInit -> JSM GType
typeGType EventInit
_ = JSM GType
gTypeEventInit
  {-# INLINE typeGType #-}

noEventInit :: Maybe EventInit
noEventInit :: Maybe EventInit
noEventInit = Maybe EventInit
forall a. Maybe a
Nothing
{-# INLINE noEventInit #-}

gTypeEventInit :: JSM GType
gTypeEventInit :: JSM GType
gTypeEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EventInit"

-- | Functions for this inteface are in "JSDOM.EventListener".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EventListener Mozilla EventListener documentation>
newtype EventListener = EventListener { EventListener -> JSVal
unEventListener :: JSVal }

instance PToJSVal EventListener where
  pToJSVal :: EventListener -> JSVal
pToJSVal = EventListener -> JSVal
unEventListener
  {-# INLINE pToJSVal #-}

instance PFromJSVal EventListener where
  pFromJSVal :: JSVal -> EventListener
pFromJSVal = JSVal -> EventListener
EventListener
  {-# INLINE pFromJSVal #-}

instance ToJSVal EventListener where
  toJSVal :: EventListener -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EventListener -> JSVal) -> EventListener -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventListener -> JSVal
unEventListener
  {-# INLINE toJSVal #-}

instance FromJSVal EventListener where
  fromJSVal :: JSVal -> JSM (Maybe EventListener)
fromJSVal JSVal
v = (JSVal -> EventListener) -> Maybe JSVal -> Maybe EventListener
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EventListener
EventListener (Maybe JSVal -> Maybe EventListener)
-> JSM (Maybe JSVal) -> JSM (Maybe EventListener)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EventListener
fromJSValUnchecked = EventListener -> JSM EventListener
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EventListener -> JSM EventListener)
-> (JSVal -> EventListener) -> JSVal -> JSM EventListener
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EventListener
EventListener
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EventListener where
  makeObject :: EventListener -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EventListener -> JSVal) -> EventListener -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventListener -> JSVal
unEventListener

instance IsGObject EventListener where
  typeGType :: EventListener -> JSM GType
typeGType EventListener
_ = JSM GType
gTypeEventListener
  {-# INLINE typeGType #-}

noEventListener :: Maybe EventListener
noEventListener :: Maybe EventListener
noEventListener = Maybe EventListener
forall a. Maybe a
Nothing
{-# INLINE noEventListener #-}

gTypeEventListener :: JSM GType
gTypeEventListener :: JSM GType
gTypeEventListener = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EventListener"

-- | Functions for this inteface are in "JSDOM.EventListenerOptions".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EventListenerOptions Mozilla EventListenerOptions documentation>
newtype EventListenerOptions = EventListenerOptions { EventListenerOptions -> JSVal
unEventListenerOptions :: JSVal }

instance PToJSVal EventListenerOptions where
  pToJSVal :: EventListenerOptions -> JSVal
pToJSVal = EventListenerOptions -> JSVal
unEventListenerOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal EventListenerOptions where
  pFromJSVal :: JSVal -> EventListenerOptions
pFromJSVal = JSVal -> EventListenerOptions
EventListenerOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal EventListenerOptions where
  toJSVal :: EventListenerOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EventListenerOptions -> JSVal)
-> EventListenerOptions
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventListenerOptions -> JSVal
unEventListenerOptions
  {-# INLINE toJSVal #-}

instance FromJSVal EventListenerOptions where
  fromJSVal :: JSVal -> JSM (Maybe EventListenerOptions)
fromJSVal JSVal
v = (JSVal -> EventListenerOptions)
-> Maybe JSVal -> Maybe EventListenerOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EventListenerOptions
EventListenerOptions (Maybe JSVal -> Maybe EventListenerOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe EventListenerOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EventListenerOptions
fromJSValUnchecked = EventListenerOptions -> JSM EventListenerOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EventListenerOptions -> JSM EventListenerOptions)
-> (JSVal -> EventListenerOptions)
-> JSVal
-> JSM EventListenerOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EventListenerOptions
EventListenerOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EventListenerOptions where
  makeObject :: EventListenerOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EventListenerOptions -> JSVal)
-> EventListenerOptions
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventListenerOptions -> JSVal
unEventListenerOptions

class (IsGObject o) => IsEventListenerOptions o
toEventListenerOptions :: IsEventListenerOptions o => o -> EventListenerOptions
toEventListenerOptions :: forall o. IsEventListenerOptions o => o -> EventListenerOptions
toEventListenerOptions = JSVal -> EventListenerOptions
EventListenerOptions (JSVal -> EventListenerOptions)
-> (o -> JSVal) -> o -> EventListenerOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsEventListenerOptions EventListenerOptions
instance IsGObject EventListenerOptions where
  typeGType :: EventListenerOptions -> JSM GType
typeGType EventListenerOptions
_ = JSM GType
gTypeEventListenerOptions
  {-# INLINE typeGType #-}

noEventListenerOptions :: Maybe EventListenerOptions
noEventListenerOptions :: Maybe EventListenerOptions
noEventListenerOptions = Maybe EventListenerOptions
forall a. Maybe a
Nothing
{-# INLINE noEventListenerOptions #-}

gTypeEventListenerOptions :: JSM GType
gTypeEventListenerOptions :: JSM GType
gTypeEventListenerOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EventListenerOptions"

-- | Functions for this inteface are in "JSDOM.EventModifierInit".
-- Base interface functions are in:
--
--     * "JSDOM.UIEventInit"
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EventModifierInit Mozilla EventModifierInit documentation>
newtype EventModifierInit = EventModifierInit { EventModifierInit -> JSVal
unEventModifierInit :: JSVal }

instance PToJSVal EventModifierInit where
  pToJSVal :: EventModifierInit -> JSVal
pToJSVal = EventModifierInit -> JSVal
unEventModifierInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal EventModifierInit where
  pFromJSVal :: JSVal -> EventModifierInit
pFromJSVal = JSVal -> EventModifierInit
EventModifierInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal EventModifierInit where
  toJSVal :: EventModifierInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EventModifierInit -> JSVal) -> EventModifierInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventModifierInit -> JSVal
unEventModifierInit
  {-# INLINE toJSVal #-}

instance FromJSVal EventModifierInit where
  fromJSVal :: JSVal -> JSM (Maybe EventModifierInit)
fromJSVal JSVal
v = (JSVal -> EventModifierInit)
-> Maybe JSVal -> Maybe EventModifierInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EventModifierInit
EventModifierInit (Maybe JSVal -> Maybe EventModifierInit)
-> JSM (Maybe JSVal) -> JSM (Maybe EventModifierInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EventModifierInit
fromJSValUnchecked = EventModifierInit -> JSM EventModifierInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EventModifierInit -> JSM EventModifierInit)
-> (JSVal -> EventModifierInit) -> JSVal -> JSM EventModifierInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EventModifierInit
EventModifierInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EventModifierInit where
  makeObject :: EventModifierInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EventModifierInit -> JSVal) -> EventModifierInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventModifierInit -> JSVal
unEventModifierInit

class (IsUIEventInit o, IsEventInit o, IsGObject o) => IsEventModifierInit o
toEventModifierInit :: IsEventModifierInit o => o -> EventModifierInit
toEventModifierInit :: forall o. IsEventModifierInit o => o -> EventModifierInit
toEventModifierInit = JSVal -> EventModifierInit
EventModifierInit (JSVal -> EventModifierInit)
-> (o -> JSVal) -> o -> EventModifierInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsEventModifierInit EventModifierInit
instance IsUIEventInit EventModifierInit
instance IsEventInit EventModifierInit
instance IsGObject EventModifierInit where
  typeGType :: EventModifierInit -> JSM GType
typeGType EventModifierInit
_ = JSM GType
gTypeEventModifierInit
  {-# INLINE typeGType #-}

noEventModifierInit :: Maybe EventModifierInit
noEventModifierInit :: Maybe EventModifierInit
noEventModifierInit = Maybe EventModifierInit
forall a. Maybe a
Nothing
{-# INLINE noEventModifierInit #-}

gTypeEventModifierInit :: JSM GType
gTypeEventModifierInit :: JSM GType
gTypeEventModifierInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EventModifierInit"

-- | Functions for this inteface are in "JSDOM.EventSource".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EventSource Mozilla EventSource documentation>
newtype EventSource = EventSource { EventSource -> JSVal
unEventSource :: JSVal }

instance PToJSVal EventSource where
  pToJSVal :: EventSource -> JSVal
pToJSVal = EventSource -> JSVal
unEventSource
  {-# INLINE pToJSVal #-}

instance PFromJSVal EventSource where
  pFromJSVal :: JSVal -> EventSource
pFromJSVal = JSVal -> EventSource
EventSource
  {-# INLINE pFromJSVal #-}

instance ToJSVal EventSource where
  toJSVal :: EventSource -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EventSource -> JSVal) -> EventSource -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventSource -> JSVal
unEventSource
  {-# INLINE toJSVal #-}

instance FromJSVal EventSource where
  fromJSVal :: JSVal -> JSM (Maybe EventSource)
fromJSVal JSVal
v = (JSVal -> EventSource) -> Maybe JSVal -> Maybe EventSource
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EventSource
EventSource (Maybe JSVal -> Maybe EventSource)
-> JSM (Maybe JSVal) -> JSM (Maybe EventSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EventSource
fromJSValUnchecked = EventSource -> JSM EventSource
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EventSource -> JSM EventSource)
-> (JSVal -> EventSource) -> JSVal -> JSM EventSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EventSource
EventSource
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EventSource where
  makeObject :: EventSource -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EventSource -> JSVal) -> EventSource -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventSource -> JSVal
unEventSource

instance IsEventTarget EventSource
instance IsGObject EventSource where
  typeGType :: EventSource -> JSM GType
typeGType EventSource
_ = JSM GType
gTypeEventSource
  {-# INLINE typeGType #-}

noEventSource :: Maybe EventSource
noEventSource :: Maybe EventSource
noEventSource = Maybe EventSource
forall a. Maybe a
Nothing
{-# INLINE noEventSource #-}

gTypeEventSource :: JSM GType
gTypeEventSource :: JSM GType
gTypeEventSource = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EventSource"

-- | Functions for this inteface are in "JSDOM.EventSourceInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EventSourceInit Mozilla EventSourceInit documentation>
newtype EventSourceInit = EventSourceInit { EventSourceInit -> JSVal
unEventSourceInit :: JSVal }

instance PToJSVal EventSourceInit where
  pToJSVal :: EventSourceInit -> JSVal
pToJSVal = EventSourceInit -> JSVal
unEventSourceInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal EventSourceInit where
  pFromJSVal :: JSVal -> EventSourceInit
pFromJSVal = JSVal -> EventSourceInit
EventSourceInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal EventSourceInit where
  toJSVal :: EventSourceInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EventSourceInit -> JSVal) -> EventSourceInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventSourceInit -> JSVal
unEventSourceInit
  {-# INLINE toJSVal #-}

instance FromJSVal EventSourceInit where
  fromJSVal :: JSVal -> JSM (Maybe EventSourceInit)
fromJSVal JSVal
v = (JSVal -> EventSourceInit) -> Maybe JSVal -> Maybe EventSourceInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EventSourceInit
EventSourceInit (Maybe JSVal -> Maybe EventSourceInit)
-> JSM (Maybe JSVal) -> JSM (Maybe EventSourceInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EventSourceInit
fromJSValUnchecked = EventSourceInit -> JSM EventSourceInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EventSourceInit -> JSM EventSourceInit)
-> (JSVal -> EventSourceInit) -> JSVal -> JSM EventSourceInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EventSourceInit
EventSourceInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EventSourceInit where
  makeObject :: EventSourceInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EventSourceInit -> JSVal) -> EventSourceInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventSourceInit -> JSVal
unEventSourceInit

instance IsGObject EventSourceInit where
  typeGType :: EventSourceInit -> JSM GType
typeGType EventSourceInit
_ = JSM GType
gTypeEventSourceInit
  {-# INLINE typeGType #-}

noEventSourceInit :: Maybe EventSourceInit
noEventSourceInit :: Maybe EventSourceInit
noEventSourceInit = Maybe EventSourceInit
forall a. Maybe a
Nothing
{-# INLINE noEventSourceInit #-}

gTypeEventSourceInit :: JSM GType
gTypeEventSourceInit :: JSM GType
gTypeEventSourceInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EventSourceInit"

-- | Functions for this inteface are in "JSDOM.EventTarget".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/EventTarget Mozilla EventTarget documentation>
newtype EventTarget = EventTarget { EventTarget -> JSVal
unEventTarget :: JSVal }

instance PToJSVal EventTarget where
  pToJSVal :: EventTarget -> JSVal
pToJSVal = EventTarget -> JSVal
unEventTarget
  {-# INLINE pToJSVal #-}

instance PFromJSVal EventTarget where
  pFromJSVal :: JSVal -> EventTarget
pFromJSVal = JSVal -> EventTarget
EventTarget
  {-# INLINE pFromJSVal #-}

instance ToJSVal EventTarget where
  toJSVal :: EventTarget -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (EventTarget -> JSVal) -> EventTarget -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventTarget -> JSVal
unEventTarget
  {-# INLINE toJSVal #-}

instance FromJSVal EventTarget where
  fromJSVal :: JSVal -> JSM (Maybe EventTarget)
fromJSVal JSVal
v = (JSVal -> EventTarget) -> Maybe JSVal -> Maybe EventTarget
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> EventTarget
EventTarget (Maybe JSVal -> Maybe EventTarget)
-> JSM (Maybe JSVal) -> JSM (Maybe EventTarget)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM EventTarget
fromJSValUnchecked = EventTarget -> JSM EventTarget
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (EventTarget -> JSM EventTarget)
-> (JSVal -> EventTarget) -> JSVal -> JSM EventTarget
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> EventTarget
EventTarget
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject EventTarget where
  makeObject :: EventTarget -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (EventTarget -> JSVal) -> EventTarget -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventTarget -> JSVal
unEventTarget

class (IsGObject o) => IsEventTarget o
toEventTarget :: IsEventTarget o => o -> EventTarget
toEventTarget :: forall o. IsEventTarget o => o -> EventTarget
toEventTarget = JSVal -> EventTarget
EventTarget (JSVal -> EventTarget) -> (o -> JSVal) -> o -> EventTarget
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsEventTarget EventTarget
instance IsGObject EventTarget where
  typeGType :: EventTarget -> JSM GType
typeGType EventTarget
_ = JSM GType
gTypeEventTarget
  {-# INLINE typeGType #-}

noEventTarget :: Maybe EventTarget
noEventTarget :: Maybe EventTarget
noEventTarget = Maybe EventTarget
forall a. Maybe a
Nothing
{-# INLINE noEventTarget #-}

gTypeEventTarget :: JSM GType
gTypeEventTarget :: JSM GType
gTypeEventTarget = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"EventTarget"

-- | Functions for this inteface are in "JSDOM.File".
-- Base interface functions are in:
--
--     * "JSDOM.Blob"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/File Mozilla File documentation>
newtype File = File { File -> JSVal
unFile :: JSVal }

instance PToJSVal File where
  pToJSVal :: File -> JSVal
pToJSVal = File -> JSVal
unFile
  {-# INLINE pToJSVal #-}

instance PFromJSVal File where
  pFromJSVal :: JSVal -> File
pFromJSVal = JSVal -> File
File
  {-# INLINE pFromJSVal #-}

instance ToJSVal File where
  toJSVal :: File -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (File -> JSVal) -> File -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. File -> JSVal
unFile
  {-# INLINE toJSVal #-}

instance FromJSVal File where
  fromJSVal :: JSVal -> JSM (Maybe File)
fromJSVal JSVal
v = (JSVal -> File) -> Maybe JSVal -> Maybe File
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> File
File (Maybe JSVal -> Maybe File)
-> JSM (Maybe JSVal) -> JSM (Maybe File)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM File
fromJSValUnchecked = File -> JSM File
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (File -> JSM File) -> (JSVal -> File) -> JSVal -> JSM File
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> File
File
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject File where
  makeObject :: File -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (File -> JSVal) -> File -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. File -> JSVal
unFile

instance IsBlob File
instance IsGObject File where
  typeGType :: File -> JSM GType
typeGType File
_ = JSM GType
gTypeFile
  {-# INLINE typeGType #-}

noFile :: Maybe File
noFile :: Maybe File
noFile = Maybe File
forall a. Maybe a
Nothing
{-# INLINE noFile #-}

gTypeFile :: JSM GType
gTypeFile :: JSM GType
gTypeFile = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"File"

-- | Functions for this inteface are in "JSDOM.FileError".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FileError Mozilla FileError documentation>
newtype FileError = FileError { FileError -> JSVal
unFileError :: JSVal }

instance PToJSVal FileError where
  pToJSVal :: FileError -> JSVal
pToJSVal = FileError -> JSVal
unFileError
  {-# INLINE pToJSVal #-}

instance PFromJSVal FileError where
  pFromJSVal :: JSVal -> FileError
pFromJSVal = JSVal -> FileError
FileError
  {-# INLINE pFromJSVal #-}

instance ToJSVal FileError where
  toJSVal :: FileError -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FileError -> JSVal) -> FileError -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileError -> JSVal
unFileError
  {-# INLINE toJSVal #-}

instance FromJSVal FileError where
  fromJSVal :: JSVal -> JSM (Maybe FileError)
fromJSVal JSVal
v = (JSVal -> FileError) -> Maybe JSVal -> Maybe FileError
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FileError
FileError (Maybe JSVal -> Maybe FileError)
-> JSM (Maybe JSVal) -> JSM (Maybe FileError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FileError
fromJSValUnchecked = FileError -> JSM FileError
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FileError -> JSM FileError)
-> (JSVal -> FileError) -> JSVal -> JSM FileError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FileError
FileError
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FileError where
  makeObject :: FileError -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FileError -> JSVal) -> FileError -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileError -> JSVal
unFileError

instance IsGObject FileError where
  typeGType :: FileError -> JSM GType
typeGType FileError
_ = JSM GType
gTypeFileError
  {-# INLINE typeGType #-}

noFileError :: Maybe FileError
noFileError :: Maybe FileError
noFileError = Maybe FileError
forall a. Maybe a
Nothing
{-# INLINE noFileError #-}

gTypeFileError :: JSM GType
gTypeFileError :: JSM GType
gTypeFileError = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FileError"

-- | Functions for this inteface are in "JSDOM.FileException".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FileException Mozilla FileException documentation>
newtype FileException = FileException { FileException -> JSVal
unFileException :: JSVal }

instance PToJSVal FileException where
  pToJSVal :: FileException -> JSVal
pToJSVal = FileException -> JSVal
unFileException
  {-# INLINE pToJSVal #-}

instance PFromJSVal FileException where
  pFromJSVal :: JSVal -> FileException
pFromJSVal = JSVal -> FileException
FileException
  {-# INLINE pFromJSVal #-}

instance ToJSVal FileException where
  toJSVal :: FileException -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FileException -> JSVal) -> FileException -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileException -> JSVal
unFileException
  {-# INLINE toJSVal #-}

instance FromJSVal FileException where
  fromJSVal :: JSVal -> JSM (Maybe FileException)
fromJSVal JSVal
v = (JSVal -> FileException) -> Maybe JSVal -> Maybe FileException
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FileException
FileException (Maybe JSVal -> Maybe FileException)
-> JSM (Maybe JSVal) -> JSM (Maybe FileException)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FileException
fromJSValUnchecked = FileException -> JSM FileException
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FileException -> JSM FileException)
-> (JSVal -> FileException) -> JSVal -> JSM FileException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FileException
FileException
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FileException where
  makeObject :: FileException -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FileException -> JSVal) -> FileException -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileException -> JSVal
unFileException

instance IsGObject FileException where
  typeGType :: FileException -> JSM GType
typeGType FileException
_ = JSM GType
gTypeFileException
  {-# INLINE typeGType #-}

noFileException :: Maybe FileException
noFileException :: Maybe FileException
noFileException = Maybe FileException
forall a. Maybe a
Nothing
{-# INLINE noFileException #-}

gTypeFileException :: JSM GType
gTypeFileException :: JSM GType
gTypeFileException = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FileException"

-- | Functions for this inteface are in "JSDOM.FileList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FileList Mozilla FileList documentation>
newtype FileList = FileList { FileList -> JSVal
unFileList :: JSVal }

instance PToJSVal FileList where
  pToJSVal :: FileList -> JSVal
pToJSVal = FileList -> JSVal
unFileList
  {-# INLINE pToJSVal #-}

instance PFromJSVal FileList where
  pFromJSVal :: JSVal -> FileList
pFromJSVal = JSVal -> FileList
FileList
  {-# INLINE pFromJSVal #-}

instance ToJSVal FileList where
  toJSVal :: FileList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FileList -> JSVal) -> FileList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileList -> JSVal
unFileList
  {-# INLINE toJSVal #-}

instance FromJSVal FileList where
  fromJSVal :: JSVal -> JSM (Maybe FileList)
fromJSVal JSVal
v = (JSVal -> FileList) -> Maybe JSVal -> Maybe FileList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FileList
FileList (Maybe JSVal -> Maybe FileList)
-> JSM (Maybe JSVal) -> JSM (Maybe FileList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FileList
fromJSValUnchecked = FileList -> JSM FileList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FileList -> JSM FileList)
-> (JSVal -> FileList) -> JSVal -> JSM FileList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FileList
FileList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FileList where
  makeObject :: FileList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FileList -> JSVal) -> FileList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileList -> JSVal
unFileList

instance IsGObject FileList where
  typeGType :: FileList -> JSM GType
typeGType FileList
_ = JSM GType
gTypeFileList
  {-# INLINE typeGType #-}

noFileList :: Maybe FileList
noFileList :: Maybe FileList
noFileList = Maybe FileList
forall a. Maybe a
Nothing
{-# INLINE noFileList #-}

gTypeFileList :: JSM GType
gTypeFileList :: JSM GType
gTypeFileList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FileList"

-- | Functions for this inteface are in "JSDOM.FilePropertyBag".
-- Base interface functions are in:
--
--     * "JSDOM.BlobPropertyBag"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FilePropertyBag Mozilla FilePropertyBag documentation>
newtype FilePropertyBag = FilePropertyBag { FilePropertyBag -> JSVal
unFilePropertyBag :: JSVal }

instance PToJSVal FilePropertyBag where
  pToJSVal :: FilePropertyBag -> JSVal
pToJSVal = FilePropertyBag -> JSVal
unFilePropertyBag
  {-# INLINE pToJSVal #-}

instance PFromJSVal FilePropertyBag where
  pFromJSVal :: JSVal -> FilePropertyBag
pFromJSVal = JSVal -> FilePropertyBag
FilePropertyBag
  {-# INLINE pFromJSVal #-}

instance ToJSVal FilePropertyBag where
  toJSVal :: FilePropertyBag -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FilePropertyBag -> JSVal) -> FilePropertyBag -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePropertyBag -> JSVal
unFilePropertyBag
  {-# INLINE toJSVal #-}

instance FromJSVal FilePropertyBag where
  fromJSVal :: JSVal -> JSM (Maybe FilePropertyBag)
fromJSVal JSVal
v = (JSVal -> FilePropertyBag) -> Maybe JSVal -> Maybe FilePropertyBag
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FilePropertyBag
FilePropertyBag (Maybe JSVal -> Maybe FilePropertyBag)
-> JSM (Maybe JSVal) -> JSM (Maybe FilePropertyBag)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FilePropertyBag
fromJSValUnchecked = FilePropertyBag -> JSM FilePropertyBag
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePropertyBag -> JSM FilePropertyBag)
-> (JSVal -> FilePropertyBag) -> JSVal -> JSM FilePropertyBag
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FilePropertyBag
FilePropertyBag
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FilePropertyBag where
  makeObject :: FilePropertyBag -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FilePropertyBag -> JSVal) -> FilePropertyBag -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePropertyBag -> JSVal
unFilePropertyBag

instance IsBlobPropertyBag FilePropertyBag
instance IsGObject FilePropertyBag where
  typeGType :: FilePropertyBag -> JSM GType
typeGType FilePropertyBag
_ = JSM GType
gTypeFilePropertyBag
  {-# INLINE typeGType #-}

noFilePropertyBag :: Maybe FilePropertyBag
noFilePropertyBag :: Maybe FilePropertyBag
noFilePropertyBag = Maybe FilePropertyBag
forall a. Maybe a
Nothing
{-# INLINE noFilePropertyBag #-}

gTypeFilePropertyBag :: JSM GType
gTypeFilePropertyBag :: JSM GType
gTypeFilePropertyBag = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FilePropertyBag"

-- | Functions for this inteface are in "JSDOM.FileReader".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FileReader Mozilla FileReader documentation>
newtype FileReader = FileReader { FileReader -> JSVal
unFileReader :: JSVal }

instance PToJSVal FileReader where
  pToJSVal :: FileReader -> JSVal
pToJSVal = FileReader -> JSVal
unFileReader
  {-# INLINE pToJSVal #-}

instance PFromJSVal FileReader where
  pFromJSVal :: JSVal -> FileReader
pFromJSVal = JSVal -> FileReader
FileReader
  {-# INLINE pFromJSVal #-}

instance ToJSVal FileReader where
  toJSVal :: FileReader -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FileReader -> JSVal) -> FileReader -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileReader -> JSVal
unFileReader
  {-# INLINE toJSVal #-}

instance FromJSVal FileReader where
  fromJSVal :: JSVal -> JSM (Maybe FileReader)
fromJSVal JSVal
v = (JSVal -> FileReader) -> Maybe JSVal -> Maybe FileReader
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FileReader
FileReader (Maybe JSVal -> Maybe FileReader)
-> JSM (Maybe JSVal) -> JSM (Maybe FileReader)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FileReader
fromJSValUnchecked = FileReader -> JSM FileReader
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FileReader -> JSM FileReader)
-> (JSVal -> FileReader) -> JSVal -> JSM FileReader
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FileReader
FileReader
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FileReader where
  makeObject :: FileReader -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FileReader -> JSVal) -> FileReader -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileReader -> JSVal
unFileReader

instance IsEventTarget FileReader
instance IsGObject FileReader where
  typeGType :: FileReader -> JSM GType
typeGType FileReader
_ = JSM GType
gTypeFileReader
  {-# INLINE typeGType #-}

noFileReader :: Maybe FileReader
noFileReader :: Maybe FileReader
noFileReader = Maybe FileReader
forall a. Maybe a
Nothing
{-# INLINE noFileReader #-}

gTypeFileReader :: JSM GType
gTypeFileReader :: JSM GType
gTypeFileReader = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FileReader"

-- | Functions for this inteface are in "JSDOM.FileReaderSync".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FileReaderSync Mozilla FileReaderSync documentation>
newtype FileReaderSync = FileReaderSync { FileReaderSync -> JSVal
unFileReaderSync :: JSVal }

instance PToJSVal FileReaderSync where
  pToJSVal :: FileReaderSync -> JSVal
pToJSVal = FileReaderSync -> JSVal
unFileReaderSync
  {-# INLINE pToJSVal #-}

instance PFromJSVal FileReaderSync where
  pFromJSVal :: JSVal -> FileReaderSync
pFromJSVal = JSVal -> FileReaderSync
FileReaderSync
  {-# INLINE pFromJSVal #-}

instance ToJSVal FileReaderSync where
  toJSVal :: FileReaderSync -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FileReaderSync -> JSVal) -> FileReaderSync -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileReaderSync -> JSVal
unFileReaderSync
  {-# INLINE toJSVal #-}

instance FromJSVal FileReaderSync where
  fromJSVal :: JSVal -> JSM (Maybe FileReaderSync)
fromJSVal JSVal
v = (JSVal -> FileReaderSync) -> Maybe JSVal -> Maybe FileReaderSync
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FileReaderSync
FileReaderSync (Maybe JSVal -> Maybe FileReaderSync)
-> JSM (Maybe JSVal) -> JSM (Maybe FileReaderSync)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FileReaderSync
fromJSValUnchecked = FileReaderSync -> JSM FileReaderSync
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FileReaderSync -> JSM FileReaderSync)
-> (JSVal -> FileReaderSync) -> JSVal -> JSM FileReaderSync
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FileReaderSync
FileReaderSync
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FileReaderSync where
  makeObject :: FileReaderSync -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FileReaderSync -> JSVal) -> FileReaderSync -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileReaderSync -> JSVal
unFileReaderSync

instance IsGObject FileReaderSync where
  typeGType :: FileReaderSync -> JSM GType
typeGType FileReaderSync
_ = JSM GType
gTypeFileReaderSync
  {-# INLINE typeGType #-}

noFileReaderSync :: Maybe FileReaderSync
noFileReaderSync :: Maybe FileReaderSync
noFileReaderSync = Maybe FileReaderSync
forall a. Maybe a
Nothing
{-# INLINE noFileReaderSync #-}

gTypeFileReaderSync :: JSM GType
gTypeFileReaderSync :: JSM GType
gTypeFileReaderSync = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FileReaderSync"

-- | Functions for this inteface are in "JSDOM.FocusEvent".
-- Base interface functions are in:
--
--     * "JSDOM.UIEvent"
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FocusEvent Mozilla FocusEvent documentation>
newtype FocusEvent = FocusEvent { FocusEvent -> JSVal
unFocusEvent :: JSVal }

instance PToJSVal FocusEvent where
  pToJSVal :: FocusEvent -> JSVal
pToJSVal = FocusEvent -> JSVal
unFocusEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal FocusEvent where
  pFromJSVal :: JSVal -> FocusEvent
pFromJSVal = JSVal -> FocusEvent
FocusEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal FocusEvent where
  toJSVal :: FocusEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FocusEvent -> JSVal) -> FocusEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FocusEvent -> JSVal
unFocusEvent
  {-# INLINE toJSVal #-}

instance FromJSVal FocusEvent where
  fromJSVal :: JSVal -> JSM (Maybe FocusEvent)
fromJSVal JSVal
v = (JSVal -> FocusEvent) -> Maybe JSVal -> Maybe FocusEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FocusEvent
FocusEvent (Maybe JSVal -> Maybe FocusEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe FocusEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FocusEvent
fromJSValUnchecked = FocusEvent -> JSM FocusEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FocusEvent -> JSM FocusEvent)
-> (JSVal -> FocusEvent) -> JSVal -> JSM FocusEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FocusEvent
FocusEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FocusEvent where
  makeObject :: FocusEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FocusEvent -> JSVal) -> FocusEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FocusEvent -> JSVal
unFocusEvent

instance IsUIEvent FocusEvent
instance IsEvent FocusEvent
instance IsGObject FocusEvent where
  typeGType :: FocusEvent -> JSM GType
typeGType FocusEvent
_ = JSM GType
gTypeFocusEvent
  {-# INLINE typeGType #-}

noFocusEvent :: Maybe FocusEvent
noFocusEvent :: Maybe FocusEvent
noFocusEvent = Maybe FocusEvent
forall a. Maybe a
Nothing
{-# INLINE noFocusEvent #-}

gTypeFocusEvent :: JSM GType
gTypeFocusEvent :: JSM GType
gTypeFocusEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FocusEvent"

-- | Functions for this inteface are in "JSDOM.FocusEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.UIEventInit"
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FocusEventInit Mozilla FocusEventInit documentation>
newtype FocusEventInit = FocusEventInit { FocusEventInit -> JSVal
unFocusEventInit :: JSVal }

instance PToJSVal FocusEventInit where
  pToJSVal :: FocusEventInit -> JSVal
pToJSVal = FocusEventInit -> JSVal
unFocusEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal FocusEventInit where
  pFromJSVal :: JSVal -> FocusEventInit
pFromJSVal = JSVal -> FocusEventInit
FocusEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal FocusEventInit where
  toJSVal :: FocusEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FocusEventInit -> JSVal) -> FocusEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FocusEventInit -> JSVal
unFocusEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal FocusEventInit where
  fromJSVal :: JSVal -> JSM (Maybe FocusEventInit)
fromJSVal JSVal
v = (JSVal -> FocusEventInit) -> Maybe JSVal -> Maybe FocusEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FocusEventInit
FocusEventInit (Maybe JSVal -> Maybe FocusEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe FocusEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FocusEventInit
fromJSValUnchecked = FocusEventInit -> JSM FocusEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FocusEventInit -> JSM FocusEventInit)
-> (JSVal -> FocusEventInit) -> JSVal -> JSM FocusEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FocusEventInit
FocusEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FocusEventInit where
  makeObject :: FocusEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FocusEventInit -> JSVal) -> FocusEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FocusEventInit -> JSVal
unFocusEventInit

instance IsUIEventInit FocusEventInit
instance IsEventInit FocusEventInit
instance IsGObject FocusEventInit where
  typeGType :: FocusEventInit -> JSM GType
typeGType FocusEventInit
_ = JSM GType
gTypeFocusEventInit
  {-# INLINE typeGType #-}

noFocusEventInit :: Maybe FocusEventInit
noFocusEventInit :: Maybe FocusEventInit
noFocusEventInit = Maybe FocusEventInit
forall a. Maybe a
Nothing
{-# INLINE noFocusEventInit #-}

gTypeFocusEventInit :: JSM GType
gTypeFocusEventInit :: JSM GType
gTypeFocusEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FocusEventInit"

-- | Functions for this inteface are in "JSDOM.FontFace".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FontFace Mozilla FontFace documentation>
newtype FontFace = FontFace { FontFace -> JSVal
unFontFace :: JSVal }

instance PToJSVal FontFace where
  pToJSVal :: FontFace -> JSVal
pToJSVal = FontFace -> JSVal
unFontFace
  {-# INLINE pToJSVal #-}

instance PFromJSVal FontFace where
  pFromJSVal :: JSVal -> FontFace
pFromJSVal = JSVal -> FontFace
FontFace
  {-# INLINE pFromJSVal #-}

instance ToJSVal FontFace where
  toJSVal :: FontFace -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FontFace -> JSVal) -> FontFace -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FontFace -> JSVal
unFontFace
  {-# INLINE toJSVal #-}

instance FromJSVal FontFace where
  fromJSVal :: JSVal -> JSM (Maybe FontFace)
fromJSVal JSVal
v = (JSVal -> FontFace) -> Maybe JSVal -> Maybe FontFace
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FontFace
FontFace (Maybe JSVal -> Maybe FontFace)
-> JSM (Maybe JSVal) -> JSM (Maybe FontFace)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FontFace
fromJSValUnchecked = FontFace -> JSM FontFace
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FontFace -> JSM FontFace)
-> (JSVal -> FontFace) -> JSVal -> JSM FontFace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FontFace
FontFace
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FontFace where
  makeObject :: FontFace -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FontFace -> JSVal) -> FontFace -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FontFace -> JSVal
unFontFace

instance IsGObject FontFace where
  typeGType :: FontFace -> JSM GType
typeGType FontFace
_ = JSM GType
gTypeFontFace
  {-# INLINE typeGType #-}

noFontFace :: Maybe FontFace
noFontFace :: Maybe FontFace
noFontFace = Maybe FontFace
forall a. Maybe a
Nothing
{-# INLINE noFontFace #-}

gTypeFontFace :: JSM GType
gTypeFontFace :: JSM GType
gTypeFontFace = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FontFace"

-- | Functions for this inteface are in "JSDOM.FontFaceDescriptors".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FontFaceDescriptors Mozilla FontFaceDescriptors documentation>
newtype FontFaceDescriptors = FontFaceDescriptors { FontFaceDescriptors -> JSVal
unFontFaceDescriptors :: JSVal }

instance PToJSVal FontFaceDescriptors where
  pToJSVal :: FontFaceDescriptors -> JSVal
pToJSVal = FontFaceDescriptors -> JSVal
unFontFaceDescriptors
  {-# INLINE pToJSVal #-}

instance PFromJSVal FontFaceDescriptors where
  pFromJSVal :: JSVal -> FontFaceDescriptors
pFromJSVal = JSVal -> FontFaceDescriptors
FontFaceDescriptors
  {-# INLINE pFromJSVal #-}

instance ToJSVal FontFaceDescriptors where
  toJSVal :: FontFaceDescriptors -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FontFaceDescriptors -> JSVal)
-> FontFaceDescriptors
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FontFaceDescriptors -> JSVal
unFontFaceDescriptors
  {-# INLINE toJSVal #-}

instance FromJSVal FontFaceDescriptors where
  fromJSVal :: JSVal -> JSM (Maybe FontFaceDescriptors)
fromJSVal JSVal
v = (JSVal -> FontFaceDescriptors)
-> Maybe JSVal -> Maybe FontFaceDescriptors
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FontFaceDescriptors
FontFaceDescriptors (Maybe JSVal -> Maybe FontFaceDescriptors)
-> JSM (Maybe JSVal) -> JSM (Maybe FontFaceDescriptors)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FontFaceDescriptors
fromJSValUnchecked = FontFaceDescriptors -> JSM FontFaceDescriptors
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FontFaceDescriptors -> JSM FontFaceDescriptors)
-> (JSVal -> FontFaceDescriptors)
-> JSVal
-> JSM FontFaceDescriptors
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FontFaceDescriptors
FontFaceDescriptors
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FontFaceDescriptors where
  makeObject :: FontFaceDescriptors -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FontFaceDescriptors -> JSVal)
-> FontFaceDescriptors
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FontFaceDescriptors -> JSVal
unFontFaceDescriptors

instance IsGObject FontFaceDescriptors where
  typeGType :: FontFaceDescriptors -> JSM GType
typeGType FontFaceDescriptors
_ = JSM GType
gTypeFontFaceDescriptors
  {-# INLINE typeGType #-}

noFontFaceDescriptors :: Maybe FontFaceDescriptors
noFontFaceDescriptors :: Maybe FontFaceDescriptors
noFontFaceDescriptors = Maybe FontFaceDescriptors
forall a. Maybe a
Nothing
{-# INLINE noFontFaceDescriptors #-}

gTypeFontFaceDescriptors :: JSM GType
gTypeFontFaceDescriptors :: JSM GType
gTypeFontFaceDescriptors = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FontFaceDescriptors"

-- | Functions for this inteface are in "JSDOM.FontFaceSet".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FontFaceSet Mozilla FontFaceSet documentation>
newtype FontFaceSet = FontFaceSet { FontFaceSet -> JSVal
unFontFaceSet :: JSVal }

instance PToJSVal FontFaceSet where
  pToJSVal :: FontFaceSet -> JSVal
pToJSVal = FontFaceSet -> JSVal
unFontFaceSet
  {-# INLINE pToJSVal #-}

instance PFromJSVal FontFaceSet where
  pFromJSVal :: JSVal -> FontFaceSet
pFromJSVal = JSVal -> FontFaceSet
FontFaceSet
  {-# INLINE pFromJSVal #-}

instance ToJSVal FontFaceSet where
  toJSVal :: FontFaceSet -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FontFaceSet -> JSVal) -> FontFaceSet -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FontFaceSet -> JSVal
unFontFaceSet
  {-# INLINE toJSVal #-}

instance FromJSVal FontFaceSet where
  fromJSVal :: JSVal -> JSM (Maybe FontFaceSet)
fromJSVal JSVal
v = (JSVal -> FontFaceSet) -> Maybe JSVal -> Maybe FontFaceSet
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FontFaceSet
FontFaceSet (Maybe JSVal -> Maybe FontFaceSet)
-> JSM (Maybe JSVal) -> JSM (Maybe FontFaceSet)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FontFaceSet
fromJSValUnchecked = FontFaceSet -> JSM FontFaceSet
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FontFaceSet -> JSM FontFaceSet)
-> (JSVal -> FontFaceSet) -> JSVal -> JSM FontFaceSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FontFaceSet
FontFaceSet
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FontFaceSet where
  makeObject :: FontFaceSet -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FontFaceSet -> JSVal) -> FontFaceSet -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FontFaceSet -> JSVal
unFontFaceSet

instance IsEventTarget FontFaceSet
instance IsGObject FontFaceSet where
  typeGType :: FontFaceSet -> JSM GType
typeGType FontFaceSet
_ = JSM GType
gTypeFontFaceSet
  {-# INLINE typeGType #-}

noFontFaceSet :: Maybe FontFaceSet
noFontFaceSet :: Maybe FontFaceSet
noFontFaceSet = Maybe FontFaceSet
forall a. Maybe a
Nothing
{-# INLINE noFontFaceSet #-}

gTypeFontFaceSet :: JSM GType
gTypeFontFaceSet :: JSM GType
gTypeFontFaceSet = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FontFaceSet"

-- | Functions for this inteface are in "JSDOM.FormData".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/FormData Mozilla FormData documentation>
newtype FormData = FormData { FormData -> JSVal
unFormData :: JSVal }

instance PToJSVal FormData where
  pToJSVal :: FormData -> JSVal
pToJSVal = FormData -> JSVal
unFormData
  {-# INLINE pToJSVal #-}

instance PFromJSVal FormData where
  pFromJSVal :: JSVal -> FormData
pFromJSVal = JSVal -> FormData
FormData
  {-# INLINE pFromJSVal #-}

instance ToJSVal FormData where
  toJSVal :: FormData -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (FormData -> JSVal) -> FormData -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FormData -> JSVal
unFormData
  {-# INLINE toJSVal #-}

instance FromJSVal FormData where
  fromJSVal :: JSVal -> JSM (Maybe FormData)
fromJSVal JSVal
v = (JSVal -> FormData) -> Maybe JSVal -> Maybe FormData
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> FormData
FormData (Maybe JSVal -> Maybe FormData)
-> JSM (Maybe JSVal) -> JSM (Maybe FormData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM FormData
fromJSValUnchecked = FormData -> JSM FormData
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (FormData -> JSM FormData)
-> (JSVal -> FormData) -> JSVal -> JSM FormData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> FormData
FormData
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject FormData where
  makeObject :: FormData -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (FormData -> JSVal) -> FormData -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FormData -> JSVal
unFormData

instance IsGObject FormData where
  typeGType :: FormData -> JSM GType
typeGType FormData
_ = JSM GType
gTypeFormData
  {-# INLINE typeGType #-}

noFormData :: Maybe FormData
noFormData :: Maybe FormData
noFormData = Maybe FormData
forall a. Maybe a
Nothing
{-# INLINE noFormData #-}

gTypeFormData :: JSM GType
gTypeFormData :: JSM GType
gTypeFormData = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"FormData"

-- | Functions for this inteface are in "JSDOM.GainNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/GainNode Mozilla GainNode documentation>
newtype GainNode = GainNode { GainNode -> JSVal
unGainNode :: JSVal }

instance PToJSVal GainNode where
  pToJSVal :: GainNode -> JSVal
pToJSVal = GainNode -> JSVal
unGainNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal GainNode where
  pFromJSVal :: JSVal -> GainNode
pFromJSVal = JSVal -> GainNode
GainNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal GainNode where
  toJSVal :: GainNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (GainNode -> JSVal) -> GainNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GainNode -> JSVal
unGainNode
  {-# INLINE toJSVal #-}

instance FromJSVal GainNode where
  fromJSVal :: JSVal -> JSM (Maybe GainNode)
fromJSVal JSVal
v = (JSVal -> GainNode) -> Maybe JSVal -> Maybe GainNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> GainNode
GainNode (Maybe JSVal -> Maybe GainNode)
-> JSM (Maybe JSVal) -> JSM (Maybe GainNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM GainNode
fromJSValUnchecked = GainNode -> JSM GainNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (GainNode -> JSM GainNode)
-> (JSVal -> GainNode) -> JSVal -> JSM GainNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> GainNode
GainNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject GainNode where
  makeObject :: GainNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (GainNode -> JSVal) -> GainNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GainNode -> JSVal
unGainNode

instance IsAudioNode GainNode
instance IsEventTarget GainNode
instance IsGObject GainNode where
  typeGType :: GainNode -> JSM GType
typeGType GainNode
_ = JSM GType
gTypeGainNode
  {-# INLINE typeGType #-}

noGainNode :: Maybe GainNode
noGainNode :: Maybe GainNode
noGainNode = Maybe GainNode
forall a. Maybe a
Nothing
{-# INLINE noGainNode #-}

gTypeGainNode :: JSM GType
gTypeGainNode :: JSM GType
gTypeGainNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"GainNode"

-- | Functions for this inteface are in "JSDOM.Gamepad".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Gamepad Mozilla Gamepad documentation>
newtype Gamepad = Gamepad { Gamepad -> JSVal
unGamepad :: JSVal }

instance PToJSVal Gamepad where
  pToJSVal :: Gamepad -> JSVal
pToJSVal = Gamepad -> JSVal
unGamepad
  {-# INLINE pToJSVal #-}

instance PFromJSVal Gamepad where
  pFromJSVal :: JSVal -> Gamepad
pFromJSVal = JSVal -> Gamepad
Gamepad
  {-# INLINE pFromJSVal #-}

instance ToJSVal Gamepad where
  toJSVal :: Gamepad -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Gamepad -> JSVal) -> Gamepad -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gamepad -> JSVal
unGamepad
  {-# INLINE toJSVal #-}

instance FromJSVal Gamepad where
  fromJSVal :: JSVal -> JSM (Maybe Gamepad)
fromJSVal JSVal
v = (JSVal -> Gamepad) -> Maybe JSVal -> Maybe Gamepad
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Gamepad
Gamepad (Maybe JSVal -> Maybe Gamepad)
-> JSM (Maybe JSVal) -> JSM (Maybe Gamepad)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Gamepad
fromJSValUnchecked = Gamepad -> JSM Gamepad
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Gamepad -> JSM Gamepad)
-> (JSVal -> Gamepad) -> JSVal -> JSM Gamepad
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Gamepad
Gamepad
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Gamepad where
  makeObject :: Gamepad -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Gamepad -> JSVal) -> Gamepad -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gamepad -> JSVal
unGamepad

instance IsGObject Gamepad where
  typeGType :: Gamepad -> JSM GType
typeGType Gamepad
_ = JSM GType
gTypeGamepad
  {-# INLINE typeGType #-}

noGamepad :: Maybe Gamepad
noGamepad :: Maybe Gamepad
noGamepad = Maybe Gamepad
forall a. Maybe a
Nothing
{-# INLINE noGamepad #-}

gTypeGamepad :: JSM GType
gTypeGamepad :: JSM GType
gTypeGamepad = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Gamepad"

-- | Functions for this inteface are in "JSDOM.GamepadButton".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/GamepadButton Mozilla GamepadButton documentation>
newtype GamepadButton = GamepadButton { GamepadButton -> JSVal
unGamepadButton :: JSVal }

instance PToJSVal GamepadButton where
  pToJSVal :: GamepadButton -> JSVal
pToJSVal = GamepadButton -> JSVal
unGamepadButton
  {-# INLINE pToJSVal #-}

instance PFromJSVal GamepadButton where
  pFromJSVal :: JSVal -> GamepadButton
pFromJSVal = JSVal -> GamepadButton
GamepadButton
  {-# INLINE pFromJSVal #-}

instance ToJSVal GamepadButton where
  toJSVal :: GamepadButton -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (GamepadButton -> JSVal) -> GamepadButton -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GamepadButton -> JSVal
unGamepadButton
  {-# INLINE toJSVal #-}

instance FromJSVal GamepadButton where
  fromJSVal :: JSVal -> JSM (Maybe GamepadButton)
fromJSVal JSVal
v = (JSVal -> GamepadButton) -> Maybe JSVal -> Maybe GamepadButton
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> GamepadButton
GamepadButton (Maybe JSVal -> Maybe GamepadButton)
-> JSM (Maybe JSVal) -> JSM (Maybe GamepadButton)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM GamepadButton
fromJSValUnchecked = GamepadButton -> JSM GamepadButton
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (GamepadButton -> JSM GamepadButton)
-> (JSVal -> GamepadButton) -> JSVal -> JSM GamepadButton
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> GamepadButton
GamepadButton
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject GamepadButton where
  makeObject :: GamepadButton -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (GamepadButton -> JSVal) -> GamepadButton -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GamepadButton -> JSVal
unGamepadButton

instance IsGObject GamepadButton where
  typeGType :: GamepadButton -> JSM GType
typeGType GamepadButton
_ = JSM GType
gTypeGamepadButton
  {-# INLINE typeGType #-}

noGamepadButton :: Maybe GamepadButton
noGamepadButton :: Maybe GamepadButton
noGamepadButton = Maybe GamepadButton
forall a. Maybe a
Nothing
{-# INLINE noGamepadButton #-}

gTypeGamepadButton :: JSM GType
gTypeGamepadButton :: JSM GType
gTypeGamepadButton = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"GamepadButton"

-- | Functions for this inteface are in "JSDOM.GamepadEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/GamepadEvent Mozilla GamepadEvent documentation>
newtype GamepadEvent = GamepadEvent { GamepadEvent -> JSVal
unGamepadEvent :: JSVal }

instance PToJSVal GamepadEvent where
  pToJSVal :: GamepadEvent -> JSVal
pToJSVal = GamepadEvent -> JSVal
unGamepadEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal GamepadEvent where
  pFromJSVal :: JSVal -> GamepadEvent
pFromJSVal = JSVal -> GamepadEvent
GamepadEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal GamepadEvent where
  toJSVal :: GamepadEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (GamepadEvent -> JSVal) -> GamepadEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GamepadEvent -> JSVal
unGamepadEvent
  {-# INLINE toJSVal #-}

instance FromJSVal GamepadEvent where
  fromJSVal :: JSVal -> JSM (Maybe GamepadEvent)
fromJSVal JSVal
v = (JSVal -> GamepadEvent) -> Maybe JSVal -> Maybe GamepadEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> GamepadEvent
GamepadEvent (Maybe JSVal -> Maybe GamepadEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe GamepadEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM GamepadEvent
fromJSValUnchecked = GamepadEvent -> JSM GamepadEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (GamepadEvent -> JSM GamepadEvent)
-> (JSVal -> GamepadEvent) -> JSVal -> JSM GamepadEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> GamepadEvent
GamepadEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject GamepadEvent where
  makeObject :: GamepadEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (GamepadEvent -> JSVal) -> GamepadEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GamepadEvent -> JSVal
unGamepadEvent

instance IsEvent GamepadEvent
instance IsGObject GamepadEvent where
  typeGType :: GamepadEvent -> JSM GType
typeGType GamepadEvent
_ = JSM GType
gTypeGamepadEvent
  {-# INLINE typeGType #-}

noGamepadEvent :: Maybe GamepadEvent
noGamepadEvent :: Maybe GamepadEvent
noGamepadEvent = Maybe GamepadEvent
forall a. Maybe a
Nothing
{-# INLINE noGamepadEvent #-}

gTypeGamepadEvent :: JSM GType
gTypeGamepadEvent :: JSM GType
gTypeGamepadEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"GamepadEvent"

-- | Functions for this inteface are in "JSDOM.GamepadEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/GamepadEventInit Mozilla GamepadEventInit documentation>
newtype GamepadEventInit = GamepadEventInit { GamepadEventInit -> JSVal
unGamepadEventInit :: JSVal }

instance PToJSVal GamepadEventInit where
  pToJSVal :: GamepadEventInit -> JSVal
pToJSVal = GamepadEventInit -> JSVal
unGamepadEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal GamepadEventInit where
  pFromJSVal :: JSVal -> GamepadEventInit
pFromJSVal = JSVal -> GamepadEventInit
GamepadEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal GamepadEventInit where
  toJSVal :: GamepadEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (GamepadEventInit -> JSVal) -> GamepadEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GamepadEventInit -> JSVal
unGamepadEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal GamepadEventInit where
  fromJSVal :: JSVal -> JSM (Maybe GamepadEventInit)
fromJSVal JSVal
v = (JSVal -> GamepadEventInit)
-> Maybe JSVal -> Maybe GamepadEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> GamepadEventInit
GamepadEventInit (Maybe JSVal -> Maybe GamepadEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe GamepadEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM GamepadEventInit
fromJSValUnchecked = GamepadEventInit -> JSM GamepadEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (GamepadEventInit -> JSM GamepadEventInit)
-> (JSVal -> GamepadEventInit) -> JSVal -> JSM GamepadEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> GamepadEventInit
GamepadEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject GamepadEventInit where
  makeObject :: GamepadEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (GamepadEventInit -> JSVal) -> GamepadEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GamepadEventInit -> JSVal
unGamepadEventInit

instance IsEventInit GamepadEventInit
instance IsGObject GamepadEventInit where
  typeGType :: GamepadEventInit -> JSM GType
typeGType GamepadEventInit
_ = JSM GType
gTypeGamepadEventInit
  {-# INLINE typeGType #-}

noGamepadEventInit :: Maybe GamepadEventInit
noGamepadEventInit :: Maybe GamepadEventInit
noGamepadEventInit = Maybe GamepadEventInit
forall a. Maybe a
Nothing
{-# INLINE noGamepadEventInit #-}

gTypeGamepadEventInit :: JSM GType
gTypeGamepadEventInit :: JSM GType
gTypeGamepadEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"GamepadEventInit"

-- | Functions for this inteface are in "JSDOM.Geolocation".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Geolocation Mozilla Geolocation documentation>
newtype Geolocation = Geolocation { Geolocation -> JSVal
unGeolocation :: JSVal }

instance PToJSVal Geolocation where
  pToJSVal :: Geolocation -> JSVal
pToJSVal = Geolocation -> JSVal
unGeolocation
  {-# INLINE pToJSVal #-}

instance PFromJSVal Geolocation where
  pFromJSVal :: JSVal -> Geolocation
pFromJSVal = JSVal -> Geolocation
Geolocation
  {-# INLINE pFromJSVal #-}

instance ToJSVal Geolocation where
  toJSVal :: Geolocation -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Geolocation -> JSVal) -> Geolocation -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Geolocation -> JSVal
unGeolocation
  {-# INLINE toJSVal #-}

instance FromJSVal Geolocation where
  fromJSVal :: JSVal -> JSM (Maybe Geolocation)
fromJSVal JSVal
v = (JSVal -> Geolocation) -> Maybe JSVal -> Maybe Geolocation
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Geolocation
Geolocation (Maybe JSVal -> Maybe Geolocation)
-> JSM (Maybe JSVal) -> JSM (Maybe Geolocation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Geolocation
fromJSValUnchecked = Geolocation -> JSM Geolocation
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Geolocation -> JSM Geolocation)
-> (JSVal -> Geolocation) -> JSVal -> JSM Geolocation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Geolocation
Geolocation
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Geolocation where
  makeObject :: Geolocation -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Geolocation -> JSVal) -> Geolocation -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Geolocation -> JSVal
unGeolocation

instance IsGObject Geolocation where
  typeGType :: Geolocation -> JSM GType
typeGType Geolocation
_ = JSM GType
gTypeGeolocation
  {-# INLINE typeGType #-}

noGeolocation :: Maybe Geolocation
noGeolocation :: Maybe Geolocation
noGeolocation = Maybe Geolocation
forall a. Maybe a
Nothing
{-# INLINE noGeolocation #-}

gTypeGeolocation :: JSM GType
gTypeGeolocation :: JSM GType
gTypeGeolocation = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Geolocation"

-- | Functions for this inteface are in "JSDOM.Geoposition".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Geoposition Mozilla Geoposition documentation>
newtype Geoposition = Geoposition { Geoposition -> JSVal
unGeoposition :: JSVal }

instance PToJSVal Geoposition where
  pToJSVal :: Geoposition -> JSVal
pToJSVal = Geoposition -> JSVal
unGeoposition
  {-# INLINE pToJSVal #-}

instance PFromJSVal Geoposition where
  pFromJSVal :: JSVal -> Geoposition
pFromJSVal = JSVal -> Geoposition
Geoposition
  {-# INLINE pFromJSVal #-}

instance ToJSVal Geoposition where
  toJSVal :: Geoposition -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Geoposition -> JSVal) -> Geoposition -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Geoposition -> JSVal
unGeoposition
  {-# INLINE toJSVal #-}

instance FromJSVal Geoposition where
  fromJSVal :: JSVal -> JSM (Maybe Geoposition)
fromJSVal JSVal
v = (JSVal -> Geoposition) -> Maybe JSVal -> Maybe Geoposition
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Geoposition
Geoposition (Maybe JSVal -> Maybe Geoposition)
-> JSM (Maybe JSVal) -> JSM (Maybe Geoposition)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Geoposition
fromJSValUnchecked = Geoposition -> JSM Geoposition
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Geoposition -> JSM Geoposition)
-> (JSVal -> Geoposition) -> JSVal -> JSM Geoposition
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Geoposition
Geoposition
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Geoposition where
  makeObject :: Geoposition -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Geoposition -> JSVal) -> Geoposition -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Geoposition -> JSVal
unGeoposition

instance IsGObject Geoposition where
  typeGType :: Geoposition -> JSM GType
typeGType Geoposition
_ = JSM GType
gTypeGeoposition
  {-# INLINE typeGType #-}

noGeoposition :: Maybe Geoposition
noGeoposition :: Maybe Geoposition
noGeoposition = Maybe Geoposition
forall a. Maybe a
Nothing
{-# INLINE noGeoposition #-}

gTypeGeoposition :: JSM GType
gTypeGeoposition :: JSM GType
gTypeGeoposition = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Geoposition"

-- | Functions for this inteface are in "JSDOM.GetRootNodeOptions".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/GetRootNodeOptions Mozilla GetRootNodeOptions documentation>
newtype GetRootNodeOptions = GetRootNodeOptions { GetRootNodeOptions -> JSVal
unGetRootNodeOptions :: JSVal }

instance PToJSVal GetRootNodeOptions where
  pToJSVal :: GetRootNodeOptions -> JSVal
pToJSVal = GetRootNodeOptions -> JSVal
unGetRootNodeOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal GetRootNodeOptions where
  pFromJSVal :: JSVal -> GetRootNodeOptions
pFromJSVal = JSVal -> GetRootNodeOptions
GetRootNodeOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal GetRootNodeOptions where
  toJSVal :: GetRootNodeOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (GetRootNodeOptions -> JSVal) -> GetRootNodeOptions -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GetRootNodeOptions -> JSVal
unGetRootNodeOptions
  {-# INLINE toJSVal #-}

instance FromJSVal GetRootNodeOptions where
  fromJSVal :: JSVal -> JSM (Maybe GetRootNodeOptions)
fromJSVal JSVal
v = (JSVal -> GetRootNodeOptions)
-> Maybe JSVal -> Maybe GetRootNodeOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> GetRootNodeOptions
GetRootNodeOptions (Maybe JSVal -> Maybe GetRootNodeOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe GetRootNodeOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM GetRootNodeOptions
fromJSValUnchecked = GetRootNodeOptions -> JSM GetRootNodeOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (GetRootNodeOptions -> JSM GetRootNodeOptions)
-> (JSVal -> GetRootNodeOptions) -> JSVal -> JSM GetRootNodeOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> GetRootNodeOptions
GetRootNodeOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject GetRootNodeOptions where
  makeObject :: GetRootNodeOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (GetRootNodeOptions -> JSVal)
-> GetRootNodeOptions
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GetRootNodeOptions -> JSVal
unGetRootNodeOptions

instance IsGObject GetRootNodeOptions where
  typeGType :: GetRootNodeOptions -> JSM GType
typeGType GetRootNodeOptions
_ = JSM GType
gTypeGetRootNodeOptions
  {-# INLINE typeGType #-}

noGetRootNodeOptions :: Maybe GetRootNodeOptions
noGetRootNodeOptions :: Maybe GetRootNodeOptions
noGetRootNodeOptions = Maybe GetRootNodeOptions
forall a. Maybe a
Nothing
{-# INLINE noGetRootNodeOptions #-}

gTypeGetRootNodeOptions :: JSM GType
gTypeGetRootNodeOptions :: JSM GType
gTypeGetRootNodeOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"GetRootNodeOptions"

-- | Functions for this inteface are in "JSDOM.GlobalCrypto".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/GlobalCrypto Mozilla GlobalCrypto documentation>
newtype GlobalCrypto = GlobalCrypto { GlobalCrypto -> JSVal
unGlobalCrypto :: JSVal }

instance PToJSVal GlobalCrypto where
  pToJSVal :: GlobalCrypto -> JSVal
pToJSVal = GlobalCrypto -> JSVal
unGlobalCrypto
  {-# INLINE pToJSVal #-}

instance PFromJSVal GlobalCrypto where
  pFromJSVal :: JSVal -> GlobalCrypto
pFromJSVal = JSVal -> GlobalCrypto
GlobalCrypto
  {-# INLINE pFromJSVal #-}

instance ToJSVal GlobalCrypto where
  toJSVal :: GlobalCrypto -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (GlobalCrypto -> JSVal) -> GlobalCrypto -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalCrypto -> JSVal
unGlobalCrypto
  {-# INLINE toJSVal #-}

instance FromJSVal GlobalCrypto where
  fromJSVal :: JSVal -> JSM (Maybe GlobalCrypto)
fromJSVal JSVal
v = (JSVal -> GlobalCrypto) -> Maybe JSVal -> Maybe GlobalCrypto
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> GlobalCrypto
GlobalCrypto (Maybe JSVal -> Maybe GlobalCrypto)
-> JSM (Maybe JSVal) -> JSM (Maybe GlobalCrypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM GlobalCrypto
fromJSValUnchecked = GlobalCrypto -> JSM GlobalCrypto
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (GlobalCrypto -> JSM GlobalCrypto)
-> (JSVal -> GlobalCrypto) -> JSVal -> JSM GlobalCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> GlobalCrypto
GlobalCrypto
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject GlobalCrypto where
  makeObject :: GlobalCrypto -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (GlobalCrypto -> JSVal) -> GlobalCrypto -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalCrypto -> JSVal
unGlobalCrypto

class (IsGObject o) => IsGlobalCrypto o
toGlobalCrypto :: IsGlobalCrypto o => o -> GlobalCrypto
toGlobalCrypto :: forall o. IsGlobalCrypto o => o -> GlobalCrypto
toGlobalCrypto = JSVal -> GlobalCrypto
GlobalCrypto (JSVal -> GlobalCrypto) -> (o -> JSVal) -> o -> GlobalCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsGlobalCrypto GlobalCrypto
instance IsGObject GlobalCrypto where
  typeGType :: GlobalCrypto -> JSM GType
typeGType GlobalCrypto
_ = JSM GType
gTypeGlobalCrypto
  {-# INLINE typeGType #-}

noGlobalCrypto :: Maybe GlobalCrypto
noGlobalCrypto :: Maybe GlobalCrypto
noGlobalCrypto = Maybe GlobalCrypto
forall a. Maybe a
Nothing
{-# INLINE noGlobalCrypto #-}

gTypeGlobalCrypto :: JSM GType
gTypeGlobalCrypto :: JSM GType
gTypeGlobalCrypto = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"GlobalCrypto"

-- | Functions for this inteface are in "JSDOM.GlobalEventHandlers".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/GlobalEventHandlers Mozilla GlobalEventHandlers documentation>
newtype GlobalEventHandlers = GlobalEventHandlers { GlobalEventHandlers -> JSVal
unGlobalEventHandlers :: JSVal }

instance PToJSVal GlobalEventHandlers where
  pToJSVal :: GlobalEventHandlers -> JSVal
pToJSVal = GlobalEventHandlers -> JSVal
unGlobalEventHandlers
  {-# INLINE pToJSVal #-}

instance PFromJSVal GlobalEventHandlers where
  pFromJSVal :: JSVal -> GlobalEventHandlers
pFromJSVal = JSVal -> GlobalEventHandlers
GlobalEventHandlers
  {-# INLINE pFromJSVal #-}

instance ToJSVal GlobalEventHandlers where
  toJSVal :: GlobalEventHandlers -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (GlobalEventHandlers -> JSVal)
-> GlobalEventHandlers
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalEventHandlers -> JSVal
unGlobalEventHandlers
  {-# INLINE toJSVal #-}

instance FromJSVal GlobalEventHandlers where
  fromJSVal :: JSVal -> JSM (Maybe GlobalEventHandlers)
fromJSVal JSVal
v = (JSVal -> GlobalEventHandlers)
-> Maybe JSVal -> Maybe GlobalEventHandlers
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> GlobalEventHandlers
GlobalEventHandlers (Maybe JSVal -> Maybe GlobalEventHandlers)
-> JSM (Maybe JSVal) -> JSM (Maybe GlobalEventHandlers)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM GlobalEventHandlers
fromJSValUnchecked = GlobalEventHandlers -> JSM GlobalEventHandlers
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (GlobalEventHandlers -> JSM GlobalEventHandlers)
-> (JSVal -> GlobalEventHandlers)
-> JSVal
-> JSM GlobalEventHandlers
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> GlobalEventHandlers
GlobalEventHandlers
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject GlobalEventHandlers where
  makeObject :: GlobalEventHandlers -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (GlobalEventHandlers -> JSVal)
-> GlobalEventHandlers
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalEventHandlers -> JSVal
unGlobalEventHandlers

class (IsGObject o) => IsGlobalEventHandlers o
toGlobalEventHandlers :: IsGlobalEventHandlers o => o -> GlobalEventHandlers
toGlobalEventHandlers :: forall o. IsGlobalEventHandlers o => o -> GlobalEventHandlers
toGlobalEventHandlers = JSVal -> GlobalEventHandlers
GlobalEventHandlers (JSVal -> GlobalEventHandlers)
-> (o -> JSVal) -> o -> GlobalEventHandlers
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsGlobalEventHandlers GlobalEventHandlers
instance IsGObject GlobalEventHandlers where
  typeGType :: GlobalEventHandlers -> JSM GType
typeGType GlobalEventHandlers
_ = JSM GType
gTypeGlobalEventHandlers
  {-# INLINE typeGType #-}

noGlobalEventHandlers :: Maybe GlobalEventHandlers
noGlobalEventHandlers :: Maybe GlobalEventHandlers
noGlobalEventHandlers = Maybe GlobalEventHandlers
forall a. Maybe a
Nothing
{-# INLINE noGlobalEventHandlers #-}

gTypeGlobalEventHandlers :: JSM GType
gTypeGlobalEventHandlers :: JSM GType
gTypeGlobalEventHandlers = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"GlobalEventHandlers"

-- | Functions for this inteface are in "JSDOM.GlobalPerformance".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/GlobalPerformance Mozilla GlobalPerformance documentation>
newtype GlobalPerformance = GlobalPerformance { GlobalPerformance -> JSVal
unGlobalPerformance :: JSVal }

instance PToJSVal GlobalPerformance where
  pToJSVal :: GlobalPerformance -> JSVal
pToJSVal = GlobalPerformance -> JSVal
unGlobalPerformance
  {-# INLINE pToJSVal #-}

instance PFromJSVal GlobalPerformance where
  pFromJSVal :: JSVal -> GlobalPerformance
pFromJSVal = JSVal -> GlobalPerformance
GlobalPerformance
  {-# INLINE pFromJSVal #-}

instance ToJSVal GlobalPerformance where
  toJSVal :: GlobalPerformance -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (GlobalPerformance -> JSVal) -> GlobalPerformance -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalPerformance -> JSVal
unGlobalPerformance
  {-# INLINE toJSVal #-}

instance FromJSVal GlobalPerformance where
  fromJSVal :: JSVal -> JSM (Maybe GlobalPerformance)
fromJSVal JSVal
v = (JSVal -> GlobalPerformance)
-> Maybe JSVal -> Maybe GlobalPerformance
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> GlobalPerformance
GlobalPerformance (Maybe JSVal -> Maybe GlobalPerformance)
-> JSM (Maybe JSVal) -> JSM (Maybe GlobalPerformance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM GlobalPerformance
fromJSValUnchecked = GlobalPerformance -> JSM GlobalPerformance
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (GlobalPerformance -> JSM GlobalPerformance)
-> (JSVal -> GlobalPerformance) -> JSVal -> JSM GlobalPerformance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> GlobalPerformance
GlobalPerformance
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject GlobalPerformance where
  makeObject :: GlobalPerformance -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (GlobalPerformance -> JSVal) -> GlobalPerformance -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalPerformance -> JSVal
unGlobalPerformance

class (IsGObject o) => IsGlobalPerformance o
toGlobalPerformance :: IsGlobalPerformance o => o -> GlobalPerformance
toGlobalPerformance :: forall o. IsGlobalPerformance o => o -> GlobalPerformance
toGlobalPerformance = JSVal -> GlobalPerformance
GlobalPerformance (JSVal -> GlobalPerformance)
-> (o -> JSVal) -> o -> GlobalPerformance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsGlobalPerformance GlobalPerformance
instance IsGObject GlobalPerformance where
  typeGType :: GlobalPerformance -> JSM GType
typeGType GlobalPerformance
_ = JSM GType
gTypeGlobalPerformance
  {-# INLINE typeGType #-}

noGlobalPerformance :: Maybe GlobalPerformance
noGlobalPerformance :: Maybe GlobalPerformance
noGlobalPerformance = Maybe GlobalPerformance
forall a. Maybe a
Nothing
{-# INLINE noGlobalPerformance #-}

gTypeGlobalPerformance :: JSM GType
gTypeGlobalPerformance :: JSM GType
gTypeGlobalPerformance = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"GlobalPerformance"

-- | Functions for this inteface are in "JSDOM.HTMLAllCollection".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLAllCollection Mozilla HTMLAllCollection documentation>
newtype HTMLAllCollection = HTMLAllCollection { HTMLAllCollection -> JSVal
unHTMLAllCollection :: JSVal }

instance PToJSVal HTMLAllCollection where
  pToJSVal :: HTMLAllCollection -> JSVal
pToJSVal = HTMLAllCollection -> JSVal
unHTMLAllCollection
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLAllCollection where
  pFromJSVal :: JSVal -> HTMLAllCollection
pFromJSVal = JSVal -> HTMLAllCollection
HTMLAllCollection
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLAllCollection where
  toJSVal :: HTMLAllCollection -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLAllCollection -> JSVal) -> HTMLAllCollection -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAllCollection -> JSVal
unHTMLAllCollection
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLAllCollection where
  fromJSVal :: JSVal -> JSM (Maybe HTMLAllCollection)
fromJSVal JSVal
v = (JSVal -> HTMLAllCollection)
-> Maybe JSVal -> Maybe HTMLAllCollection
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLAllCollection
HTMLAllCollection (Maybe JSVal -> Maybe HTMLAllCollection)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLAllCollection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLAllCollection
fromJSValUnchecked = HTMLAllCollection -> JSM HTMLAllCollection
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLAllCollection -> JSM HTMLAllCollection)
-> (JSVal -> HTMLAllCollection) -> JSVal -> JSM HTMLAllCollection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLAllCollection
HTMLAllCollection
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLAllCollection where
  makeObject :: HTMLAllCollection -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLAllCollection -> JSVal) -> HTMLAllCollection -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAllCollection -> JSVal
unHTMLAllCollection

instance IsGObject HTMLAllCollection where
  typeGType :: HTMLAllCollection -> JSM GType
typeGType HTMLAllCollection
_ = JSM GType
gTypeHTMLAllCollection
  {-# INLINE typeGType #-}

noHTMLAllCollection :: Maybe HTMLAllCollection
noHTMLAllCollection :: Maybe HTMLAllCollection
noHTMLAllCollection = Maybe HTMLAllCollection
forall a. Maybe a
Nothing
{-# INLINE noHTMLAllCollection #-}

gTypeHTMLAllCollection :: JSM GType
gTypeHTMLAllCollection :: JSM GType
gTypeHTMLAllCollection = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLAllCollection"

-- | Functions for this inteface are in "JSDOM.HTMLAnchorElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.HTMLHyperlinkElementUtils"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLAnchorElement Mozilla HTMLAnchorElement documentation>
newtype HTMLAnchorElement = HTMLAnchorElement { HTMLAnchorElement -> JSVal
unHTMLAnchorElement :: JSVal }

instance PToJSVal HTMLAnchorElement where
  pToJSVal :: HTMLAnchorElement -> JSVal
pToJSVal = HTMLAnchorElement -> JSVal
unHTMLAnchorElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLAnchorElement where
  pFromJSVal :: JSVal -> HTMLAnchorElement
pFromJSVal = JSVal -> HTMLAnchorElement
HTMLAnchorElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLAnchorElement where
  toJSVal :: HTMLAnchorElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLAnchorElement -> JSVal) -> HTMLAnchorElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAnchorElement -> JSVal
unHTMLAnchorElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLAnchorElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLAnchorElement)
fromJSVal JSVal
v = (JSVal -> HTMLAnchorElement)
-> Maybe JSVal -> Maybe HTMLAnchorElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLAnchorElement
HTMLAnchorElement (Maybe JSVal -> Maybe HTMLAnchorElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLAnchorElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLAnchorElement
fromJSValUnchecked = HTMLAnchorElement -> JSM HTMLAnchorElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLAnchorElement -> JSM HTMLAnchorElement)
-> (JSVal -> HTMLAnchorElement) -> JSVal -> JSM HTMLAnchorElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLAnchorElement
HTMLAnchorElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLAnchorElement where
  makeObject :: HTMLAnchorElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLAnchorElement -> JSVal) -> HTMLAnchorElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAnchorElement -> JSVal
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 :: HTMLAnchorElement -> JSM GType
typeGType HTMLAnchorElement
_ = JSM GType
gTypeHTMLAnchorElement
  {-# INLINE typeGType #-}

noHTMLAnchorElement :: Maybe HTMLAnchorElement
noHTMLAnchorElement :: Maybe HTMLAnchorElement
noHTMLAnchorElement = Maybe HTMLAnchorElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLAnchorElement #-}

gTypeHTMLAnchorElement :: JSM GType
gTypeHTMLAnchorElement :: JSM GType
gTypeHTMLAnchorElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLAnchorElement"

-- | Functions for this inteface are in "JSDOM.HTMLAppletElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLAppletElement Mozilla HTMLAppletElement documentation>
newtype HTMLAppletElement = HTMLAppletElement { HTMLAppletElement -> JSVal
unHTMLAppletElement :: JSVal }

instance PToJSVal HTMLAppletElement where
  pToJSVal :: HTMLAppletElement -> JSVal
pToJSVal = HTMLAppletElement -> JSVal
unHTMLAppletElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLAppletElement where
  pFromJSVal :: JSVal -> HTMLAppletElement
pFromJSVal = JSVal -> HTMLAppletElement
HTMLAppletElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLAppletElement where
  toJSVal :: HTMLAppletElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLAppletElement -> JSVal) -> HTMLAppletElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAppletElement -> JSVal
unHTMLAppletElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLAppletElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLAppletElement)
fromJSVal JSVal
v = (JSVal -> HTMLAppletElement)
-> Maybe JSVal -> Maybe HTMLAppletElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLAppletElement
HTMLAppletElement (Maybe JSVal -> Maybe HTMLAppletElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLAppletElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLAppletElement
fromJSValUnchecked = HTMLAppletElement -> JSM HTMLAppletElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLAppletElement -> JSM HTMLAppletElement)
-> (JSVal -> HTMLAppletElement) -> JSVal -> JSM HTMLAppletElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLAppletElement
HTMLAppletElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLAppletElement where
  makeObject :: HTMLAppletElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLAppletElement -> JSVal) -> HTMLAppletElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAppletElement -> JSVal
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 :: HTMLAppletElement -> JSM GType
typeGType HTMLAppletElement
_ = JSM GType
gTypeHTMLAppletElement
  {-# INLINE typeGType #-}

noHTMLAppletElement :: Maybe HTMLAppletElement
noHTMLAppletElement :: Maybe HTMLAppletElement
noHTMLAppletElement = Maybe HTMLAppletElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLAppletElement #-}

gTypeHTMLAppletElement :: JSM GType
gTypeHTMLAppletElement :: JSM GType
gTypeHTMLAppletElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLAppletElement"

-- | Functions for this inteface are in "JSDOM.HTMLAreaElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.HTMLHyperlinkElementUtils"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLAreaElement Mozilla HTMLAreaElement documentation>
newtype HTMLAreaElement = HTMLAreaElement { HTMLAreaElement -> JSVal
unHTMLAreaElement :: JSVal }

instance PToJSVal HTMLAreaElement where
  pToJSVal :: HTMLAreaElement -> JSVal
pToJSVal = HTMLAreaElement -> JSVal
unHTMLAreaElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLAreaElement where
  pFromJSVal :: JSVal -> HTMLAreaElement
pFromJSVal = JSVal -> HTMLAreaElement
HTMLAreaElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLAreaElement where
  toJSVal :: HTMLAreaElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLAreaElement -> JSVal) -> HTMLAreaElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAreaElement -> JSVal
unHTMLAreaElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLAreaElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLAreaElement)
fromJSVal JSVal
v = (JSVal -> HTMLAreaElement) -> Maybe JSVal -> Maybe HTMLAreaElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLAreaElement
HTMLAreaElement (Maybe JSVal -> Maybe HTMLAreaElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLAreaElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLAreaElement
fromJSValUnchecked = HTMLAreaElement -> JSM HTMLAreaElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLAreaElement -> JSM HTMLAreaElement)
-> (JSVal -> HTMLAreaElement) -> JSVal -> JSM HTMLAreaElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLAreaElement
HTMLAreaElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLAreaElement where
  makeObject :: HTMLAreaElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLAreaElement -> JSVal) -> HTMLAreaElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAreaElement -> JSVal
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 :: HTMLAreaElement -> JSM GType
typeGType HTMLAreaElement
_ = JSM GType
gTypeHTMLAreaElement
  {-# INLINE typeGType #-}

noHTMLAreaElement :: Maybe HTMLAreaElement
noHTMLAreaElement :: Maybe HTMLAreaElement
noHTMLAreaElement = Maybe HTMLAreaElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLAreaElement #-}

gTypeHTMLAreaElement :: JSM GType
gTypeHTMLAreaElement :: JSM GType
gTypeHTMLAreaElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLAreaElement"

-- | Functions for this inteface are in "JSDOM.HTMLAttachmentElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLAttachmentElement Mozilla HTMLAttachmentElement documentation>
newtype HTMLAttachmentElement = HTMLAttachmentElement { HTMLAttachmentElement -> JSVal
unHTMLAttachmentElement :: JSVal }

instance PToJSVal HTMLAttachmentElement where
  pToJSVal :: HTMLAttachmentElement -> JSVal
pToJSVal = HTMLAttachmentElement -> JSVal
unHTMLAttachmentElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLAttachmentElement where
  pFromJSVal :: JSVal -> HTMLAttachmentElement
pFromJSVal = JSVal -> HTMLAttachmentElement
HTMLAttachmentElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLAttachmentElement where
  toJSVal :: HTMLAttachmentElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLAttachmentElement -> JSVal)
-> HTMLAttachmentElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAttachmentElement -> JSVal
unHTMLAttachmentElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLAttachmentElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLAttachmentElement)
fromJSVal JSVal
v = (JSVal -> HTMLAttachmentElement)
-> Maybe JSVal -> Maybe HTMLAttachmentElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLAttachmentElement
HTMLAttachmentElement (Maybe JSVal -> Maybe HTMLAttachmentElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLAttachmentElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLAttachmentElement
fromJSValUnchecked = HTMLAttachmentElement -> JSM HTMLAttachmentElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLAttachmentElement -> JSM HTMLAttachmentElement)
-> (JSVal -> HTMLAttachmentElement)
-> JSVal
-> JSM HTMLAttachmentElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLAttachmentElement
HTMLAttachmentElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLAttachmentElement where
  makeObject :: HTMLAttachmentElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLAttachmentElement -> JSVal)
-> HTMLAttachmentElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAttachmentElement -> JSVal
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 :: HTMLAttachmentElement -> JSM GType
typeGType HTMLAttachmentElement
_ = JSM GType
gTypeHTMLAttachmentElement
  {-# INLINE typeGType #-}

noHTMLAttachmentElement :: Maybe HTMLAttachmentElement
noHTMLAttachmentElement :: Maybe HTMLAttachmentElement
noHTMLAttachmentElement = Maybe HTMLAttachmentElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLAttachmentElement #-}

gTypeHTMLAttachmentElement :: JSM GType
gTypeHTMLAttachmentElement :: JSM GType
gTypeHTMLAttachmentElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLAttachmentElement"

-- | Functions for this inteface are in "JSDOM.HTMLAudioElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLMediaElement"
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLAudioElement Mozilla HTMLAudioElement documentation>
newtype HTMLAudioElement = HTMLAudioElement { HTMLAudioElement -> JSVal
unHTMLAudioElement :: JSVal }

instance PToJSVal HTMLAudioElement where
  pToJSVal :: HTMLAudioElement -> JSVal
pToJSVal = HTMLAudioElement -> JSVal
unHTMLAudioElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLAudioElement where
  pFromJSVal :: JSVal -> HTMLAudioElement
pFromJSVal = JSVal -> HTMLAudioElement
HTMLAudioElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLAudioElement where
  toJSVal :: HTMLAudioElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLAudioElement -> JSVal) -> HTMLAudioElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAudioElement -> JSVal
unHTMLAudioElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLAudioElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLAudioElement)
fromJSVal JSVal
v = (JSVal -> HTMLAudioElement)
-> Maybe JSVal -> Maybe HTMLAudioElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLAudioElement
HTMLAudioElement (Maybe JSVal -> Maybe HTMLAudioElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLAudioElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLAudioElement
fromJSValUnchecked = HTMLAudioElement -> JSM HTMLAudioElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLAudioElement -> JSM HTMLAudioElement)
-> (JSVal -> HTMLAudioElement) -> JSVal -> JSM HTMLAudioElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLAudioElement
HTMLAudioElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLAudioElement where
  makeObject :: HTMLAudioElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLAudioElement -> JSVal) -> HTMLAudioElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLAudioElement -> JSVal
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 :: HTMLAudioElement -> JSM GType
typeGType HTMLAudioElement
_ = JSM GType
gTypeHTMLAudioElement
  {-# INLINE typeGType #-}

noHTMLAudioElement :: Maybe HTMLAudioElement
noHTMLAudioElement :: Maybe HTMLAudioElement
noHTMLAudioElement = Maybe HTMLAudioElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLAudioElement #-}

gTypeHTMLAudioElement :: JSM GType
gTypeHTMLAudioElement :: JSM GType
gTypeHTMLAudioElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLAudioElement"

-- | Functions for this inteface are in "JSDOM.HTMLBRElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLBRElement Mozilla HTMLBRElement documentation>
newtype HTMLBRElement = HTMLBRElement { HTMLBRElement -> JSVal
unHTMLBRElement :: JSVal }

instance PToJSVal HTMLBRElement where
  pToJSVal :: HTMLBRElement -> JSVal
pToJSVal = HTMLBRElement -> JSVal
unHTMLBRElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLBRElement where
  pFromJSVal :: JSVal -> HTMLBRElement
pFromJSVal = JSVal -> HTMLBRElement
HTMLBRElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLBRElement where
  toJSVal :: HTMLBRElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLBRElement -> JSVal) -> HTMLBRElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLBRElement -> JSVal
unHTMLBRElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLBRElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLBRElement)
fromJSVal JSVal
v = (JSVal -> HTMLBRElement) -> Maybe JSVal -> Maybe HTMLBRElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLBRElement
HTMLBRElement (Maybe JSVal -> Maybe HTMLBRElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLBRElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLBRElement
fromJSValUnchecked = HTMLBRElement -> JSM HTMLBRElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLBRElement -> JSM HTMLBRElement)
-> (JSVal -> HTMLBRElement) -> JSVal -> JSM HTMLBRElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLBRElement
HTMLBRElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLBRElement where
  makeObject :: HTMLBRElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLBRElement -> JSVal) -> HTMLBRElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLBRElement -> JSVal
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 :: HTMLBRElement -> JSM GType
typeGType HTMLBRElement
_ = JSM GType
gTypeHTMLBRElement
  {-# INLINE typeGType #-}

noHTMLBRElement :: Maybe HTMLBRElement
noHTMLBRElement :: Maybe HTMLBRElement
noHTMLBRElement = Maybe HTMLBRElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLBRElement #-}

gTypeHTMLBRElement :: JSM GType
gTypeHTMLBRElement :: JSM GType
gTypeHTMLBRElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLBRElement"

-- | Functions for this inteface are in "JSDOM.HTMLBaseElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLBaseElement Mozilla HTMLBaseElement documentation>
newtype HTMLBaseElement = HTMLBaseElement { HTMLBaseElement -> JSVal
unHTMLBaseElement :: JSVal }

instance PToJSVal HTMLBaseElement where
  pToJSVal :: HTMLBaseElement -> JSVal
pToJSVal = HTMLBaseElement -> JSVal
unHTMLBaseElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLBaseElement where
  pFromJSVal :: JSVal -> HTMLBaseElement
pFromJSVal = JSVal -> HTMLBaseElement
HTMLBaseElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLBaseElement where
  toJSVal :: HTMLBaseElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLBaseElement -> JSVal) -> HTMLBaseElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLBaseElement -> JSVal
unHTMLBaseElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLBaseElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLBaseElement)
fromJSVal JSVal
v = (JSVal -> HTMLBaseElement) -> Maybe JSVal -> Maybe HTMLBaseElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLBaseElement
HTMLBaseElement (Maybe JSVal -> Maybe HTMLBaseElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLBaseElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLBaseElement
fromJSValUnchecked = HTMLBaseElement -> JSM HTMLBaseElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLBaseElement -> JSM HTMLBaseElement)
-> (JSVal -> HTMLBaseElement) -> JSVal -> JSM HTMLBaseElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLBaseElement
HTMLBaseElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLBaseElement where
  makeObject :: HTMLBaseElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLBaseElement -> JSVal) -> HTMLBaseElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLBaseElement -> JSVal
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 :: HTMLBaseElement -> JSM GType
typeGType HTMLBaseElement
_ = JSM GType
gTypeHTMLBaseElement
  {-# INLINE typeGType #-}

noHTMLBaseElement :: Maybe HTMLBaseElement
noHTMLBaseElement :: Maybe HTMLBaseElement
noHTMLBaseElement = Maybe HTMLBaseElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLBaseElement #-}

gTypeHTMLBaseElement :: JSM GType
gTypeHTMLBaseElement :: JSM GType
gTypeHTMLBaseElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLBaseElement"

-- | Functions for this inteface are in "JSDOM.HTMLBodyElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.WindowEventHandlers"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLBodyElement Mozilla HTMLBodyElement documentation>
newtype HTMLBodyElement = HTMLBodyElement { HTMLBodyElement -> JSVal
unHTMLBodyElement :: JSVal }

instance PToJSVal HTMLBodyElement where
  pToJSVal :: HTMLBodyElement -> JSVal
pToJSVal = HTMLBodyElement -> JSVal
unHTMLBodyElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLBodyElement where
  pFromJSVal :: JSVal -> HTMLBodyElement
pFromJSVal = JSVal -> HTMLBodyElement
HTMLBodyElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLBodyElement where
  toJSVal :: HTMLBodyElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLBodyElement -> JSVal) -> HTMLBodyElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLBodyElement -> JSVal
unHTMLBodyElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLBodyElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLBodyElement)
fromJSVal JSVal
v = (JSVal -> HTMLBodyElement) -> Maybe JSVal -> Maybe HTMLBodyElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLBodyElement
HTMLBodyElement (Maybe JSVal -> Maybe HTMLBodyElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLBodyElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLBodyElement
fromJSValUnchecked = HTMLBodyElement -> JSM HTMLBodyElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLBodyElement -> JSM HTMLBodyElement)
-> (JSVal -> HTMLBodyElement) -> JSVal -> JSM HTMLBodyElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLBodyElement
HTMLBodyElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLBodyElement where
  makeObject :: HTMLBodyElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLBodyElement -> JSVal) -> HTMLBodyElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLBodyElement -> JSVal
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 :: HTMLBodyElement -> JSM GType
typeGType HTMLBodyElement
_ = JSM GType
gTypeHTMLBodyElement
  {-# INLINE typeGType #-}

noHTMLBodyElement :: Maybe HTMLBodyElement
noHTMLBodyElement :: Maybe HTMLBodyElement
noHTMLBodyElement = Maybe HTMLBodyElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLBodyElement #-}

gTypeHTMLBodyElement :: JSM GType
gTypeHTMLBodyElement :: JSM GType
gTypeHTMLBodyElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLBodyElement"

-- | Functions for this inteface are in "JSDOM.HTMLButtonElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLButtonElement Mozilla HTMLButtonElement documentation>
newtype HTMLButtonElement = HTMLButtonElement { HTMLButtonElement -> JSVal
unHTMLButtonElement :: JSVal }

instance PToJSVal HTMLButtonElement where
  pToJSVal :: HTMLButtonElement -> JSVal
pToJSVal = HTMLButtonElement -> JSVal
unHTMLButtonElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLButtonElement where
  pFromJSVal :: JSVal -> HTMLButtonElement
pFromJSVal = JSVal -> HTMLButtonElement
HTMLButtonElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLButtonElement where
  toJSVal :: HTMLButtonElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLButtonElement -> JSVal) -> HTMLButtonElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLButtonElement -> JSVal
unHTMLButtonElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLButtonElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLButtonElement)
fromJSVal JSVal
v = (JSVal -> HTMLButtonElement)
-> Maybe JSVal -> Maybe HTMLButtonElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLButtonElement
HTMLButtonElement (Maybe JSVal -> Maybe HTMLButtonElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLButtonElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLButtonElement
fromJSValUnchecked = HTMLButtonElement -> JSM HTMLButtonElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLButtonElement -> JSM HTMLButtonElement)
-> (JSVal -> HTMLButtonElement) -> JSVal -> JSM HTMLButtonElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLButtonElement
HTMLButtonElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLButtonElement where
  makeObject :: HTMLButtonElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLButtonElement -> JSVal) -> HTMLButtonElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLButtonElement -> JSVal
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 :: HTMLButtonElement -> JSM GType
typeGType HTMLButtonElement
_ = JSM GType
gTypeHTMLButtonElement
  {-# INLINE typeGType #-}

noHTMLButtonElement :: Maybe HTMLButtonElement
noHTMLButtonElement :: Maybe HTMLButtonElement
noHTMLButtonElement = Maybe HTMLButtonElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLButtonElement #-}

gTypeHTMLButtonElement :: JSM GType
gTypeHTMLButtonElement :: JSM GType
gTypeHTMLButtonElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLButtonElement"

-- | Functions for this inteface are in "JSDOM.HTMLCanvasElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLCanvasElement Mozilla HTMLCanvasElement documentation>
newtype HTMLCanvasElement = HTMLCanvasElement { HTMLCanvasElement -> JSVal
unHTMLCanvasElement :: JSVal }

instance PToJSVal HTMLCanvasElement where
  pToJSVal :: HTMLCanvasElement -> JSVal
pToJSVal = HTMLCanvasElement -> JSVal
unHTMLCanvasElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLCanvasElement where
  pFromJSVal :: JSVal -> HTMLCanvasElement
pFromJSVal = JSVal -> HTMLCanvasElement
HTMLCanvasElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLCanvasElement where
  toJSVal :: HTMLCanvasElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLCanvasElement -> JSVal) -> HTMLCanvasElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLCanvasElement -> JSVal
unHTMLCanvasElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLCanvasElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLCanvasElement)
fromJSVal JSVal
v = (JSVal -> HTMLCanvasElement)
-> Maybe JSVal -> Maybe HTMLCanvasElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLCanvasElement
HTMLCanvasElement (Maybe JSVal -> Maybe HTMLCanvasElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLCanvasElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLCanvasElement
fromJSValUnchecked = HTMLCanvasElement -> JSM HTMLCanvasElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLCanvasElement -> JSM HTMLCanvasElement)
-> (JSVal -> HTMLCanvasElement) -> JSVal -> JSM HTMLCanvasElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLCanvasElement
HTMLCanvasElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLCanvasElement where
  makeObject :: HTMLCanvasElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLCanvasElement -> JSVal) -> HTMLCanvasElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLCanvasElement -> JSVal
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 :: HTMLCanvasElement -> JSM GType
typeGType HTMLCanvasElement
_ = JSM GType
gTypeHTMLCanvasElement
  {-# INLINE typeGType #-}

noHTMLCanvasElement :: Maybe HTMLCanvasElement
noHTMLCanvasElement :: Maybe HTMLCanvasElement
noHTMLCanvasElement = Maybe HTMLCanvasElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLCanvasElement #-}

gTypeHTMLCanvasElement :: JSM GType
gTypeHTMLCanvasElement :: JSM GType
gTypeHTMLCanvasElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLCanvasElement"

-- | Functions for this inteface are in "JSDOM.HTMLCollection".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLCollection Mozilla HTMLCollection documentation>
newtype HTMLCollection = HTMLCollection { HTMLCollection -> JSVal
unHTMLCollection :: JSVal }

instance PToJSVal HTMLCollection where
  pToJSVal :: HTMLCollection -> JSVal
pToJSVal = HTMLCollection -> JSVal
unHTMLCollection
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLCollection where
  pFromJSVal :: JSVal -> HTMLCollection
pFromJSVal = JSVal -> HTMLCollection
HTMLCollection
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLCollection where
  toJSVal :: HTMLCollection -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLCollection -> JSVal) -> HTMLCollection -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLCollection -> JSVal
unHTMLCollection
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLCollection where
  fromJSVal :: JSVal -> JSM (Maybe HTMLCollection)
fromJSVal JSVal
v = (JSVal -> HTMLCollection) -> Maybe JSVal -> Maybe HTMLCollection
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLCollection
HTMLCollection (Maybe JSVal -> Maybe HTMLCollection)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLCollection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLCollection
fromJSValUnchecked = HTMLCollection -> JSM HTMLCollection
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLCollection -> JSM HTMLCollection)
-> (JSVal -> HTMLCollection) -> JSVal -> JSM HTMLCollection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLCollection
HTMLCollection
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLCollection where
  makeObject :: HTMLCollection -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLCollection -> JSVal) -> HTMLCollection -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLCollection -> JSVal
unHTMLCollection

class (IsGObject o) => IsHTMLCollection o
toHTMLCollection :: IsHTMLCollection o => o -> HTMLCollection
toHTMLCollection :: forall o. IsHTMLCollection o => o -> HTMLCollection
toHTMLCollection = JSVal -> HTMLCollection
HTMLCollection (JSVal -> HTMLCollection) -> (o -> JSVal) -> o -> HTMLCollection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsHTMLCollection HTMLCollection
instance IsGObject HTMLCollection where
  typeGType :: HTMLCollection -> JSM GType
typeGType HTMLCollection
_ = JSM GType
gTypeHTMLCollection
  {-# INLINE typeGType #-}

noHTMLCollection :: Maybe HTMLCollection
noHTMLCollection :: Maybe HTMLCollection
noHTMLCollection = Maybe HTMLCollection
forall a. Maybe a
Nothing
{-# INLINE noHTMLCollection #-}

gTypeHTMLCollection :: JSM GType
gTypeHTMLCollection :: JSM GType
gTypeHTMLCollection = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLCollection"

-- | Functions for this inteface are in "JSDOM.HTMLDListElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLDListElement Mozilla HTMLDListElement documentation>
newtype HTMLDListElement = HTMLDListElement { HTMLDListElement -> JSVal
unHTMLDListElement :: JSVal }

instance PToJSVal HTMLDListElement where
  pToJSVal :: HTMLDListElement -> JSVal
pToJSVal = HTMLDListElement -> JSVal
unHTMLDListElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLDListElement where
  pFromJSVal :: JSVal -> HTMLDListElement
pFromJSVal = JSVal -> HTMLDListElement
HTMLDListElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLDListElement where
  toJSVal :: HTMLDListElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLDListElement -> JSVal) -> HTMLDListElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDListElement -> JSVal
unHTMLDListElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLDListElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLDListElement)
fromJSVal JSVal
v = (JSVal -> HTMLDListElement)
-> Maybe JSVal -> Maybe HTMLDListElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLDListElement
HTMLDListElement (Maybe JSVal -> Maybe HTMLDListElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLDListElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLDListElement
fromJSValUnchecked = HTMLDListElement -> JSM HTMLDListElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLDListElement -> JSM HTMLDListElement)
-> (JSVal -> HTMLDListElement) -> JSVal -> JSM HTMLDListElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLDListElement
HTMLDListElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLDListElement where
  makeObject :: HTMLDListElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLDListElement -> JSVal) -> HTMLDListElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDListElement -> JSVal
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 :: HTMLDListElement -> JSM GType
typeGType HTMLDListElement
_ = JSM GType
gTypeHTMLDListElement
  {-# INLINE typeGType #-}

noHTMLDListElement :: Maybe HTMLDListElement
noHTMLDListElement :: Maybe HTMLDListElement
noHTMLDListElement = Maybe HTMLDListElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLDListElement #-}

gTypeHTMLDListElement :: JSM GType
gTypeHTMLDListElement :: JSM GType
gTypeHTMLDListElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLDListElement"

-- | Functions for this inteface are in "JSDOM.HTMLDataElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLDataElement Mozilla HTMLDataElement documentation>
newtype HTMLDataElement = HTMLDataElement { HTMLDataElement -> JSVal
unHTMLDataElement :: JSVal }

instance PToJSVal HTMLDataElement where
  pToJSVal :: HTMLDataElement -> JSVal
pToJSVal = HTMLDataElement -> JSVal
unHTMLDataElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLDataElement where
  pFromJSVal :: JSVal -> HTMLDataElement
pFromJSVal = JSVal -> HTMLDataElement
HTMLDataElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLDataElement where
  toJSVal :: HTMLDataElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLDataElement -> JSVal) -> HTMLDataElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDataElement -> JSVal
unHTMLDataElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLDataElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLDataElement)
fromJSVal JSVal
v = (JSVal -> HTMLDataElement) -> Maybe JSVal -> Maybe HTMLDataElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLDataElement
HTMLDataElement (Maybe JSVal -> Maybe HTMLDataElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLDataElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLDataElement
fromJSValUnchecked = HTMLDataElement -> JSM HTMLDataElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLDataElement -> JSM HTMLDataElement)
-> (JSVal -> HTMLDataElement) -> JSVal -> JSM HTMLDataElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLDataElement
HTMLDataElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLDataElement where
  makeObject :: HTMLDataElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLDataElement -> JSVal) -> HTMLDataElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDataElement -> JSVal
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 :: HTMLDataElement -> JSM GType
typeGType HTMLDataElement
_ = JSM GType
gTypeHTMLDataElement
  {-# INLINE typeGType #-}

noHTMLDataElement :: Maybe HTMLDataElement
noHTMLDataElement :: Maybe HTMLDataElement
noHTMLDataElement = Maybe HTMLDataElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLDataElement #-}

gTypeHTMLDataElement :: JSM GType
gTypeHTMLDataElement :: JSM GType
gTypeHTMLDataElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLDataElement"

-- | Functions for this inteface are in "JSDOM.HTMLDataListElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLDataListElement Mozilla HTMLDataListElement documentation>
newtype HTMLDataListElement = HTMLDataListElement { HTMLDataListElement -> JSVal
unHTMLDataListElement :: JSVal }

instance PToJSVal HTMLDataListElement where
  pToJSVal :: HTMLDataListElement -> JSVal
pToJSVal = HTMLDataListElement -> JSVal
unHTMLDataListElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLDataListElement where
  pFromJSVal :: JSVal -> HTMLDataListElement
pFromJSVal = JSVal -> HTMLDataListElement
HTMLDataListElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLDataListElement where
  toJSVal :: HTMLDataListElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLDataListElement -> JSVal)
-> HTMLDataListElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDataListElement -> JSVal
unHTMLDataListElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLDataListElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLDataListElement)
fromJSVal JSVal
v = (JSVal -> HTMLDataListElement)
-> Maybe JSVal -> Maybe HTMLDataListElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLDataListElement
HTMLDataListElement (Maybe JSVal -> Maybe HTMLDataListElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLDataListElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLDataListElement
fromJSValUnchecked = HTMLDataListElement -> JSM HTMLDataListElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLDataListElement -> JSM HTMLDataListElement)
-> (JSVal -> HTMLDataListElement)
-> JSVal
-> JSM HTMLDataListElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLDataListElement
HTMLDataListElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLDataListElement where
  makeObject :: HTMLDataListElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLDataListElement -> JSVal)
-> HTMLDataListElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDataListElement -> JSVal
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 :: HTMLDataListElement -> JSM GType
typeGType HTMLDataListElement
_ = JSM GType
gTypeHTMLDataListElement
  {-# INLINE typeGType #-}

noHTMLDataListElement :: Maybe HTMLDataListElement
noHTMLDataListElement :: Maybe HTMLDataListElement
noHTMLDataListElement = Maybe HTMLDataListElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLDataListElement #-}

gTypeHTMLDataListElement :: JSM GType
gTypeHTMLDataListElement :: JSM GType
gTypeHTMLDataListElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLDataListElement"

-- | Functions for this inteface are in "JSDOM.HTMLDetailsElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLDetailsElement Mozilla HTMLDetailsElement documentation>
newtype HTMLDetailsElement = HTMLDetailsElement { HTMLDetailsElement -> JSVal
unHTMLDetailsElement :: JSVal }

instance PToJSVal HTMLDetailsElement where
  pToJSVal :: HTMLDetailsElement -> JSVal
pToJSVal = HTMLDetailsElement -> JSVal
unHTMLDetailsElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLDetailsElement where
  pFromJSVal :: JSVal -> HTMLDetailsElement
pFromJSVal = JSVal -> HTMLDetailsElement
HTMLDetailsElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLDetailsElement where
  toJSVal :: HTMLDetailsElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLDetailsElement -> JSVal) -> HTMLDetailsElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDetailsElement -> JSVal
unHTMLDetailsElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLDetailsElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLDetailsElement)
fromJSVal JSVal
v = (JSVal -> HTMLDetailsElement)
-> Maybe JSVal -> Maybe HTMLDetailsElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLDetailsElement
HTMLDetailsElement (Maybe JSVal -> Maybe HTMLDetailsElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLDetailsElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLDetailsElement
fromJSValUnchecked = HTMLDetailsElement -> JSM HTMLDetailsElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLDetailsElement -> JSM HTMLDetailsElement)
-> (JSVal -> HTMLDetailsElement) -> JSVal -> JSM HTMLDetailsElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLDetailsElement
HTMLDetailsElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLDetailsElement where
  makeObject :: HTMLDetailsElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLDetailsElement -> JSVal)
-> HTMLDetailsElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDetailsElement -> JSVal
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 :: HTMLDetailsElement -> JSM GType
typeGType HTMLDetailsElement
_ = JSM GType
gTypeHTMLDetailsElement
  {-# INLINE typeGType #-}

noHTMLDetailsElement :: Maybe HTMLDetailsElement
noHTMLDetailsElement :: Maybe HTMLDetailsElement
noHTMLDetailsElement = Maybe HTMLDetailsElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLDetailsElement #-}

gTypeHTMLDetailsElement :: JSM GType
gTypeHTMLDetailsElement :: JSM GType
gTypeHTMLDetailsElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLDetailsElement"

-- | Functions for this inteface are in "JSDOM.HTMLDirectoryElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLDirectoryElement Mozilla HTMLDirectoryElement documentation>
newtype HTMLDirectoryElement = HTMLDirectoryElement { HTMLDirectoryElement -> JSVal
unHTMLDirectoryElement :: JSVal }

instance PToJSVal HTMLDirectoryElement where
  pToJSVal :: HTMLDirectoryElement -> JSVal
pToJSVal = HTMLDirectoryElement -> JSVal
unHTMLDirectoryElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLDirectoryElement where
  pFromJSVal :: JSVal -> HTMLDirectoryElement
pFromJSVal = JSVal -> HTMLDirectoryElement
HTMLDirectoryElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLDirectoryElement where
  toJSVal :: HTMLDirectoryElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLDirectoryElement -> JSVal)
-> HTMLDirectoryElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDirectoryElement -> JSVal
unHTMLDirectoryElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLDirectoryElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLDirectoryElement)
fromJSVal JSVal
v = (JSVal -> HTMLDirectoryElement)
-> Maybe JSVal -> Maybe HTMLDirectoryElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLDirectoryElement
HTMLDirectoryElement (Maybe JSVal -> Maybe HTMLDirectoryElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLDirectoryElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLDirectoryElement
fromJSValUnchecked = HTMLDirectoryElement -> JSM HTMLDirectoryElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLDirectoryElement -> JSM HTMLDirectoryElement)
-> (JSVal -> HTMLDirectoryElement)
-> JSVal
-> JSM HTMLDirectoryElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLDirectoryElement
HTMLDirectoryElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLDirectoryElement where
  makeObject :: HTMLDirectoryElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLDirectoryElement -> JSVal)
-> HTMLDirectoryElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDirectoryElement -> JSVal
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 :: HTMLDirectoryElement -> JSM GType
typeGType HTMLDirectoryElement
_ = JSM GType
gTypeHTMLDirectoryElement
  {-# INLINE typeGType #-}

noHTMLDirectoryElement :: Maybe HTMLDirectoryElement
noHTMLDirectoryElement :: Maybe HTMLDirectoryElement
noHTMLDirectoryElement = Maybe HTMLDirectoryElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLDirectoryElement #-}

gTypeHTMLDirectoryElement :: JSM GType
gTypeHTMLDirectoryElement :: JSM GType
gTypeHTMLDirectoryElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLDirectoryElement"

-- | Functions for this inteface are in "JSDOM.HTMLDivElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLDivElement Mozilla HTMLDivElement documentation>
newtype HTMLDivElement = HTMLDivElement { HTMLDivElement -> JSVal
unHTMLDivElement :: JSVal }

instance PToJSVal HTMLDivElement where
  pToJSVal :: HTMLDivElement -> JSVal
pToJSVal = HTMLDivElement -> JSVal
unHTMLDivElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLDivElement where
  pFromJSVal :: JSVal -> HTMLDivElement
pFromJSVal = JSVal -> HTMLDivElement
HTMLDivElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLDivElement where
  toJSVal :: HTMLDivElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLDivElement -> JSVal) -> HTMLDivElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDivElement -> JSVal
unHTMLDivElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLDivElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLDivElement)
fromJSVal JSVal
v = (JSVal -> HTMLDivElement) -> Maybe JSVal -> Maybe HTMLDivElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLDivElement
HTMLDivElement (Maybe JSVal -> Maybe HTMLDivElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLDivElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLDivElement
fromJSValUnchecked = HTMLDivElement -> JSM HTMLDivElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLDivElement -> JSM HTMLDivElement)
-> (JSVal -> HTMLDivElement) -> JSVal -> JSM HTMLDivElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLDivElement
HTMLDivElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLDivElement where
  makeObject :: HTMLDivElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLDivElement -> JSVal) -> HTMLDivElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDivElement -> JSVal
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 :: HTMLDivElement -> JSM GType
typeGType HTMLDivElement
_ = JSM GType
gTypeHTMLDivElement
  {-# INLINE typeGType #-}

noHTMLDivElement :: Maybe HTMLDivElement
noHTMLDivElement :: Maybe HTMLDivElement
noHTMLDivElement = Maybe HTMLDivElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLDivElement #-}

gTypeHTMLDivElement :: JSM GType
gTypeHTMLDivElement :: JSM GType
gTypeHTMLDivElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLDivElement"

-- | Functions for this inteface are in "JSDOM.HTMLDocument".
-- Base interface functions are in:
--
--     * "JSDOM.Document"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.DocumentOrShadowRoot"
--     * "JSDOM.NonElementParentNode"
--     * "JSDOM.ParentNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLDocument Mozilla HTMLDocument documentation>
newtype HTMLDocument = HTMLDocument { HTMLDocument -> JSVal
unHTMLDocument :: JSVal }

instance PToJSVal HTMLDocument where
  pToJSVal :: HTMLDocument -> JSVal
pToJSVal = HTMLDocument -> JSVal
unHTMLDocument
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLDocument where
  pFromJSVal :: JSVal -> HTMLDocument
pFromJSVal = JSVal -> HTMLDocument
HTMLDocument
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLDocument where
  toJSVal :: HTMLDocument -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLDocument -> JSVal) -> HTMLDocument -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDocument -> JSVal
unHTMLDocument
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLDocument where
  fromJSVal :: JSVal -> JSM (Maybe HTMLDocument)
fromJSVal JSVal
v = (JSVal -> HTMLDocument) -> Maybe JSVal -> Maybe HTMLDocument
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLDocument
HTMLDocument (Maybe JSVal -> Maybe HTMLDocument)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLDocument)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLDocument
fromJSValUnchecked = HTMLDocument -> JSM HTMLDocument
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLDocument -> JSM HTMLDocument)
-> (JSVal -> HTMLDocument) -> JSVal -> JSM HTMLDocument
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLDocument
HTMLDocument
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLDocument where
  makeObject :: HTMLDocument -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLDocument -> JSVal) -> HTMLDocument -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLDocument -> JSVal
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 :: HTMLDocument -> JSM GType
typeGType HTMLDocument
_ = JSM GType
gTypeHTMLDocument
  {-# INLINE typeGType #-}

noHTMLDocument :: Maybe HTMLDocument
noHTMLDocument :: Maybe HTMLDocument
noHTMLDocument = Maybe HTMLDocument
forall a. Maybe a
Nothing
{-# INLINE noHTMLDocument #-}

gTypeHTMLDocument :: JSM GType
gTypeHTMLDocument :: JSM GType
gTypeHTMLDocument = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLDocument"

-- | Functions for this inteface are in "JSDOM.HTMLElement".
-- Base interface functions are in:
--
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLElement Mozilla HTMLElement documentation>
newtype HTMLElement = HTMLElement { HTMLElement -> JSVal
unHTMLElement :: JSVal }

instance PToJSVal HTMLElement where
  pToJSVal :: HTMLElement -> JSVal
pToJSVal = HTMLElement -> JSVal
unHTMLElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLElement where
  pFromJSVal :: JSVal -> HTMLElement
pFromJSVal = JSVal -> HTMLElement
HTMLElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLElement where
  toJSVal :: HTMLElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLElement -> JSVal) -> HTMLElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLElement -> JSVal
unHTMLElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLElement)
fromJSVal JSVal
v = (JSVal -> HTMLElement) -> Maybe JSVal -> Maybe HTMLElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLElement
HTMLElement (Maybe JSVal -> Maybe HTMLElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLElement
fromJSValUnchecked = HTMLElement -> JSM HTMLElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLElement -> JSM HTMLElement)
-> (JSVal -> HTMLElement) -> JSVal -> JSM HTMLElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLElement
HTMLElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLElement where
  makeObject :: HTMLElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLElement -> JSVal) -> HTMLElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLElement -> JSVal
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 :: forall o. IsHTMLElement o => o -> HTMLElement
toHTMLElement = JSVal -> HTMLElement
HTMLElement (JSVal -> HTMLElement) -> (o -> JSVal) -> o -> HTMLElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: HTMLElement -> JSM GType
typeGType HTMLElement
_ = JSM GType
gTypeHTMLElement
  {-# INLINE typeGType #-}

noHTMLElement :: Maybe HTMLElement
noHTMLElement :: Maybe HTMLElement
noHTMLElement = Maybe HTMLElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLElement #-}

gTypeHTMLElement :: JSM GType
gTypeHTMLElement :: JSM GType
gTypeHTMLElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLElement"

-- | Functions for this inteface are in "JSDOM.HTMLEmbedElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLEmbedElement Mozilla HTMLEmbedElement documentation>
newtype HTMLEmbedElement = HTMLEmbedElement { HTMLEmbedElement -> JSVal
unHTMLEmbedElement :: JSVal }

instance PToJSVal HTMLEmbedElement where
  pToJSVal :: HTMLEmbedElement -> JSVal
pToJSVal = HTMLEmbedElement -> JSVal
unHTMLEmbedElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLEmbedElement where
  pFromJSVal :: JSVal -> HTMLEmbedElement
pFromJSVal = JSVal -> HTMLEmbedElement
HTMLEmbedElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLEmbedElement where
  toJSVal :: HTMLEmbedElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLEmbedElement -> JSVal) -> HTMLEmbedElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLEmbedElement -> JSVal
unHTMLEmbedElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLEmbedElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLEmbedElement)
fromJSVal JSVal
v = (JSVal -> HTMLEmbedElement)
-> Maybe JSVal -> Maybe HTMLEmbedElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLEmbedElement
HTMLEmbedElement (Maybe JSVal -> Maybe HTMLEmbedElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLEmbedElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLEmbedElement
fromJSValUnchecked = HTMLEmbedElement -> JSM HTMLEmbedElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLEmbedElement -> JSM HTMLEmbedElement)
-> (JSVal -> HTMLEmbedElement) -> JSVal -> JSM HTMLEmbedElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLEmbedElement
HTMLEmbedElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLEmbedElement where
  makeObject :: HTMLEmbedElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLEmbedElement -> JSVal) -> HTMLEmbedElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLEmbedElement -> JSVal
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 :: HTMLEmbedElement -> JSM GType
typeGType HTMLEmbedElement
_ = JSM GType
gTypeHTMLEmbedElement
  {-# INLINE typeGType #-}

noHTMLEmbedElement :: Maybe HTMLEmbedElement
noHTMLEmbedElement :: Maybe HTMLEmbedElement
noHTMLEmbedElement = Maybe HTMLEmbedElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLEmbedElement #-}

gTypeHTMLEmbedElement :: JSM GType
gTypeHTMLEmbedElement :: JSM GType
gTypeHTMLEmbedElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLEmbedElement"

-- | Functions for this inteface are in "JSDOM.HTMLFieldSetElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLFieldSetElement Mozilla HTMLFieldSetElement documentation>
newtype HTMLFieldSetElement = HTMLFieldSetElement { HTMLFieldSetElement -> JSVal
unHTMLFieldSetElement :: JSVal }

instance PToJSVal HTMLFieldSetElement where
  pToJSVal :: HTMLFieldSetElement -> JSVal
pToJSVal = HTMLFieldSetElement -> JSVal
unHTMLFieldSetElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLFieldSetElement where
  pFromJSVal :: JSVal -> HTMLFieldSetElement
pFromJSVal = JSVal -> HTMLFieldSetElement
HTMLFieldSetElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLFieldSetElement where
  toJSVal :: HTMLFieldSetElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLFieldSetElement -> JSVal)
-> HTMLFieldSetElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFieldSetElement -> JSVal
unHTMLFieldSetElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLFieldSetElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLFieldSetElement)
fromJSVal JSVal
v = (JSVal -> HTMLFieldSetElement)
-> Maybe JSVal -> Maybe HTMLFieldSetElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLFieldSetElement
HTMLFieldSetElement (Maybe JSVal -> Maybe HTMLFieldSetElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLFieldSetElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLFieldSetElement
fromJSValUnchecked = HTMLFieldSetElement -> JSM HTMLFieldSetElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLFieldSetElement -> JSM HTMLFieldSetElement)
-> (JSVal -> HTMLFieldSetElement)
-> JSVal
-> JSM HTMLFieldSetElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLFieldSetElement
HTMLFieldSetElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLFieldSetElement where
  makeObject :: HTMLFieldSetElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLFieldSetElement -> JSVal)
-> HTMLFieldSetElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFieldSetElement -> JSVal
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 :: HTMLFieldSetElement -> JSM GType
typeGType HTMLFieldSetElement
_ = JSM GType
gTypeHTMLFieldSetElement
  {-# INLINE typeGType #-}

noHTMLFieldSetElement :: Maybe HTMLFieldSetElement
noHTMLFieldSetElement :: Maybe HTMLFieldSetElement
noHTMLFieldSetElement = Maybe HTMLFieldSetElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLFieldSetElement #-}

gTypeHTMLFieldSetElement :: JSM GType
gTypeHTMLFieldSetElement :: JSM GType
gTypeHTMLFieldSetElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLFieldSetElement"

-- | Functions for this inteface are in "JSDOM.HTMLFontElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLFontElement Mozilla HTMLFontElement documentation>
newtype HTMLFontElement = HTMLFontElement { HTMLFontElement -> JSVal
unHTMLFontElement :: JSVal }

instance PToJSVal HTMLFontElement where
  pToJSVal :: HTMLFontElement -> JSVal
pToJSVal = HTMLFontElement -> JSVal
unHTMLFontElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLFontElement where
  pFromJSVal :: JSVal -> HTMLFontElement
pFromJSVal = JSVal -> HTMLFontElement
HTMLFontElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLFontElement where
  toJSVal :: HTMLFontElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLFontElement -> JSVal) -> HTMLFontElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFontElement -> JSVal
unHTMLFontElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLFontElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLFontElement)
fromJSVal JSVal
v = (JSVal -> HTMLFontElement) -> Maybe JSVal -> Maybe HTMLFontElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLFontElement
HTMLFontElement (Maybe JSVal -> Maybe HTMLFontElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLFontElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLFontElement
fromJSValUnchecked = HTMLFontElement -> JSM HTMLFontElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLFontElement -> JSM HTMLFontElement)
-> (JSVal -> HTMLFontElement) -> JSVal -> JSM HTMLFontElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLFontElement
HTMLFontElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLFontElement where
  makeObject :: HTMLFontElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLFontElement -> JSVal) -> HTMLFontElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFontElement -> JSVal
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 :: HTMLFontElement -> JSM GType
typeGType HTMLFontElement
_ = JSM GType
gTypeHTMLFontElement
  {-# INLINE typeGType #-}

noHTMLFontElement :: Maybe HTMLFontElement
noHTMLFontElement :: Maybe HTMLFontElement
noHTMLFontElement = Maybe HTMLFontElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLFontElement #-}

gTypeHTMLFontElement :: JSM GType
gTypeHTMLFontElement :: JSM GType
gTypeHTMLFontElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLFontElement"

-- | Functions for this inteface are in "JSDOM.HTMLFormControlsCollection".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLCollection"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLFormControlsCollection Mozilla HTMLFormControlsCollection documentation>
newtype HTMLFormControlsCollection = HTMLFormControlsCollection { HTMLFormControlsCollection -> JSVal
unHTMLFormControlsCollection :: JSVal }

instance PToJSVal HTMLFormControlsCollection where
  pToJSVal :: HTMLFormControlsCollection -> JSVal
pToJSVal = HTMLFormControlsCollection -> JSVal
unHTMLFormControlsCollection
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLFormControlsCollection where
  pFromJSVal :: JSVal -> HTMLFormControlsCollection
pFromJSVal = JSVal -> HTMLFormControlsCollection
HTMLFormControlsCollection
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLFormControlsCollection where
  toJSVal :: HTMLFormControlsCollection -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLFormControlsCollection -> JSVal)
-> HTMLFormControlsCollection
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFormControlsCollection -> JSVal
unHTMLFormControlsCollection
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLFormControlsCollection where
  fromJSVal :: JSVal -> JSM (Maybe HTMLFormControlsCollection)
fromJSVal JSVal
v = (JSVal -> HTMLFormControlsCollection)
-> Maybe JSVal -> Maybe HTMLFormControlsCollection
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLFormControlsCollection
HTMLFormControlsCollection (Maybe JSVal -> Maybe HTMLFormControlsCollection)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLFormControlsCollection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLFormControlsCollection
fromJSValUnchecked = HTMLFormControlsCollection -> JSM HTMLFormControlsCollection
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLFormControlsCollection -> JSM HTMLFormControlsCollection)
-> (JSVal -> HTMLFormControlsCollection)
-> JSVal
-> JSM HTMLFormControlsCollection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLFormControlsCollection
HTMLFormControlsCollection
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLFormControlsCollection where
  makeObject :: HTMLFormControlsCollection -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLFormControlsCollection -> JSVal)
-> HTMLFormControlsCollection
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFormControlsCollection -> JSVal
unHTMLFormControlsCollection

instance IsHTMLCollection HTMLFormControlsCollection
instance IsGObject HTMLFormControlsCollection where
  typeGType :: HTMLFormControlsCollection -> JSM GType
typeGType HTMLFormControlsCollection
_ = JSM GType
gTypeHTMLFormControlsCollection
  {-# INLINE typeGType #-}

noHTMLFormControlsCollection :: Maybe HTMLFormControlsCollection
noHTMLFormControlsCollection :: Maybe HTMLFormControlsCollection
noHTMLFormControlsCollection = Maybe HTMLFormControlsCollection
forall a. Maybe a
Nothing
{-# INLINE noHTMLFormControlsCollection #-}

gTypeHTMLFormControlsCollection :: JSM GType
gTypeHTMLFormControlsCollection :: JSM GType
gTypeHTMLFormControlsCollection = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLFormControlsCollection"

-- | Functions for this inteface are in "JSDOM.HTMLFormElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLFormElement Mozilla HTMLFormElement documentation>
newtype HTMLFormElement = HTMLFormElement { HTMLFormElement -> JSVal
unHTMLFormElement :: JSVal }

instance PToJSVal HTMLFormElement where
  pToJSVal :: HTMLFormElement -> JSVal
pToJSVal = HTMLFormElement -> JSVal
unHTMLFormElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLFormElement where
  pFromJSVal :: JSVal -> HTMLFormElement
pFromJSVal = JSVal -> HTMLFormElement
HTMLFormElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLFormElement where
  toJSVal :: HTMLFormElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLFormElement -> JSVal) -> HTMLFormElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFormElement -> JSVal
unHTMLFormElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLFormElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLFormElement)
fromJSVal JSVal
v = (JSVal -> HTMLFormElement) -> Maybe JSVal -> Maybe HTMLFormElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLFormElement
HTMLFormElement (Maybe JSVal -> Maybe HTMLFormElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLFormElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLFormElement
fromJSValUnchecked = HTMLFormElement -> JSM HTMLFormElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLFormElement -> JSM HTMLFormElement)
-> (JSVal -> HTMLFormElement) -> JSVal -> JSM HTMLFormElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLFormElement
HTMLFormElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLFormElement where
  makeObject :: HTMLFormElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLFormElement -> JSVal) -> HTMLFormElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFormElement -> JSVal
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 :: HTMLFormElement -> JSM GType
typeGType HTMLFormElement
_ = JSM GType
gTypeHTMLFormElement
  {-# INLINE typeGType #-}

noHTMLFormElement :: Maybe HTMLFormElement
noHTMLFormElement :: Maybe HTMLFormElement
noHTMLFormElement = Maybe HTMLFormElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLFormElement #-}

gTypeHTMLFormElement :: JSM GType
gTypeHTMLFormElement :: JSM GType
gTypeHTMLFormElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLFormElement"

-- | Functions for this inteface are in "JSDOM.HTMLFrameElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLFrameElement Mozilla HTMLFrameElement documentation>
newtype HTMLFrameElement = HTMLFrameElement { HTMLFrameElement -> JSVal
unHTMLFrameElement :: JSVal }

instance PToJSVal HTMLFrameElement where
  pToJSVal :: HTMLFrameElement -> JSVal
pToJSVal = HTMLFrameElement -> JSVal
unHTMLFrameElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLFrameElement where
  pFromJSVal :: JSVal -> HTMLFrameElement
pFromJSVal = JSVal -> HTMLFrameElement
HTMLFrameElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLFrameElement where
  toJSVal :: HTMLFrameElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLFrameElement -> JSVal) -> HTMLFrameElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFrameElement -> JSVal
unHTMLFrameElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLFrameElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLFrameElement)
fromJSVal JSVal
v = (JSVal -> HTMLFrameElement)
-> Maybe JSVal -> Maybe HTMLFrameElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLFrameElement
HTMLFrameElement (Maybe JSVal -> Maybe HTMLFrameElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLFrameElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLFrameElement
fromJSValUnchecked = HTMLFrameElement -> JSM HTMLFrameElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLFrameElement -> JSM HTMLFrameElement)
-> (JSVal -> HTMLFrameElement) -> JSVal -> JSM HTMLFrameElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLFrameElement
HTMLFrameElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLFrameElement where
  makeObject :: HTMLFrameElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLFrameElement -> JSVal) -> HTMLFrameElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFrameElement -> JSVal
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 :: HTMLFrameElement -> JSM GType
typeGType HTMLFrameElement
_ = JSM GType
gTypeHTMLFrameElement
  {-# INLINE typeGType #-}

noHTMLFrameElement :: Maybe HTMLFrameElement
noHTMLFrameElement :: Maybe HTMLFrameElement
noHTMLFrameElement = Maybe HTMLFrameElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLFrameElement #-}

gTypeHTMLFrameElement :: JSM GType
gTypeHTMLFrameElement :: JSM GType
gTypeHTMLFrameElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLFrameElement"

-- | Functions for this inteface are in "JSDOM.HTMLFrameSetElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.WindowEventHandlers"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLFrameSetElement Mozilla HTMLFrameSetElement documentation>
newtype HTMLFrameSetElement = HTMLFrameSetElement { HTMLFrameSetElement -> JSVal
unHTMLFrameSetElement :: JSVal }

instance PToJSVal HTMLFrameSetElement where
  pToJSVal :: HTMLFrameSetElement -> JSVal
pToJSVal = HTMLFrameSetElement -> JSVal
unHTMLFrameSetElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLFrameSetElement where
  pFromJSVal :: JSVal -> HTMLFrameSetElement
pFromJSVal = JSVal -> HTMLFrameSetElement
HTMLFrameSetElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLFrameSetElement where
  toJSVal :: HTMLFrameSetElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLFrameSetElement -> JSVal)
-> HTMLFrameSetElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFrameSetElement -> JSVal
unHTMLFrameSetElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLFrameSetElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLFrameSetElement)
fromJSVal JSVal
v = (JSVal -> HTMLFrameSetElement)
-> Maybe JSVal -> Maybe HTMLFrameSetElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLFrameSetElement
HTMLFrameSetElement (Maybe JSVal -> Maybe HTMLFrameSetElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLFrameSetElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLFrameSetElement
fromJSValUnchecked = HTMLFrameSetElement -> JSM HTMLFrameSetElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLFrameSetElement -> JSM HTMLFrameSetElement)
-> (JSVal -> HTMLFrameSetElement)
-> JSVal
-> JSM HTMLFrameSetElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLFrameSetElement
HTMLFrameSetElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLFrameSetElement where
  makeObject :: HTMLFrameSetElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLFrameSetElement -> JSVal)
-> HTMLFrameSetElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLFrameSetElement -> JSVal
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 :: HTMLFrameSetElement -> JSM GType
typeGType HTMLFrameSetElement
_ = JSM GType
gTypeHTMLFrameSetElement
  {-# INLINE typeGType #-}

noHTMLFrameSetElement :: Maybe HTMLFrameSetElement
noHTMLFrameSetElement :: Maybe HTMLFrameSetElement
noHTMLFrameSetElement = Maybe HTMLFrameSetElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLFrameSetElement #-}

gTypeHTMLFrameSetElement :: JSM GType
gTypeHTMLFrameSetElement :: JSM GType
gTypeHTMLFrameSetElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLFrameSetElement"

-- | Functions for this inteface are in "JSDOM.HTMLHRElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLHRElement Mozilla HTMLHRElement documentation>
newtype HTMLHRElement = HTMLHRElement { HTMLHRElement -> JSVal
unHTMLHRElement :: JSVal }

instance PToJSVal HTMLHRElement where
  pToJSVal :: HTMLHRElement -> JSVal
pToJSVal = HTMLHRElement -> JSVal
unHTMLHRElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLHRElement where
  pFromJSVal :: JSVal -> HTMLHRElement
pFromJSVal = JSVal -> HTMLHRElement
HTMLHRElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLHRElement where
  toJSVal :: HTMLHRElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLHRElement -> JSVal) -> HTMLHRElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLHRElement -> JSVal
unHTMLHRElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLHRElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLHRElement)
fromJSVal JSVal
v = (JSVal -> HTMLHRElement) -> Maybe JSVal -> Maybe HTMLHRElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLHRElement
HTMLHRElement (Maybe JSVal -> Maybe HTMLHRElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLHRElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLHRElement
fromJSValUnchecked = HTMLHRElement -> JSM HTMLHRElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLHRElement -> JSM HTMLHRElement)
-> (JSVal -> HTMLHRElement) -> JSVal -> JSM HTMLHRElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLHRElement
HTMLHRElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLHRElement where
  makeObject :: HTMLHRElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLHRElement -> JSVal) -> HTMLHRElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLHRElement -> JSVal
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 :: HTMLHRElement -> JSM GType
typeGType HTMLHRElement
_ = JSM GType
gTypeHTMLHRElement
  {-# INLINE typeGType #-}

noHTMLHRElement :: Maybe HTMLHRElement
noHTMLHRElement :: Maybe HTMLHRElement
noHTMLHRElement = Maybe HTMLHRElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLHRElement #-}

gTypeHTMLHRElement :: JSM GType
gTypeHTMLHRElement :: JSM GType
gTypeHTMLHRElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLHRElement"

-- | Functions for this inteface are in "JSDOM.HTMLHeadElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLHeadElement Mozilla HTMLHeadElement documentation>
newtype HTMLHeadElement = HTMLHeadElement { HTMLHeadElement -> JSVal
unHTMLHeadElement :: JSVal }

instance PToJSVal HTMLHeadElement where
  pToJSVal :: HTMLHeadElement -> JSVal
pToJSVal = HTMLHeadElement -> JSVal
unHTMLHeadElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLHeadElement where
  pFromJSVal :: JSVal -> HTMLHeadElement
pFromJSVal = JSVal -> HTMLHeadElement
HTMLHeadElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLHeadElement where
  toJSVal :: HTMLHeadElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLHeadElement -> JSVal) -> HTMLHeadElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLHeadElement -> JSVal
unHTMLHeadElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLHeadElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLHeadElement)
fromJSVal JSVal
v = (JSVal -> HTMLHeadElement) -> Maybe JSVal -> Maybe HTMLHeadElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLHeadElement
HTMLHeadElement (Maybe JSVal -> Maybe HTMLHeadElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLHeadElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLHeadElement
fromJSValUnchecked = HTMLHeadElement -> JSM HTMLHeadElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLHeadElement -> JSM HTMLHeadElement)
-> (JSVal -> HTMLHeadElement) -> JSVal -> JSM HTMLHeadElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLHeadElement
HTMLHeadElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLHeadElement where
  makeObject :: HTMLHeadElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLHeadElement -> JSVal) -> HTMLHeadElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLHeadElement -> JSVal
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 :: HTMLHeadElement -> JSM GType
typeGType HTMLHeadElement
_ = JSM GType
gTypeHTMLHeadElement
  {-# INLINE typeGType #-}

noHTMLHeadElement :: Maybe HTMLHeadElement
noHTMLHeadElement :: Maybe HTMLHeadElement
noHTMLHeadElement = Maybe HTMLHeadElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLHeadElement #-}

gTypeHTMLHeadElement :: JSM GType
gTypeHTMLHeadElement :: JSM GType
gTypeHTMLHeadElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLHeadElement"

-- | Functions for this inteface are in "JSDOM.HTMLHeadingElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLHeadingElement Mozilla HTMLHeadingElement documentation>
newtype HTMLHeadingElement = HTMLHeadingElement { HTMLHeadingElement -> JSVal
unHTMLHeadingElement :: JSVal }

instance PToJSVal HTMLHeadingElement where
  pToJSVal :: HTMLHeadingElement -> JSVal
pToJSVal = HTMLHeadingElement -> JSVal
unHTMLHeadingElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLHeadingElement where
  pFromJSVal :: JSVal -> HTMLHeadingElement
pFromJSVal = JSVal -> HTMLHeadingElement
HTMLHeadingElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLHeadingElement where
  toJSVal :: HTMLHeadingElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLHeadingElement -> JSVal) -> HTMLHeadingElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLHeadingElement -> JSVal
unHTMLHeadingElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLHeadingElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLHeadingElement)
fromJSVal JSVal
v = (JSVal -> HTMLHeadingElement)
-> Maybe JSVal -> Maybe HTMLHeadingElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLHeadingElement
HTMLHeadingElement (Maybe JSVal -> Maybe HTMLHeadingElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLHeadingElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLHeadingElement
fromJSValUnchecked = HTMLHeadingElement -> JSM HTMLHeadingElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLHeadingElement -> JSM HTMLHeadingElement)
-> (JSVal -> HTMLHeadingElement) -> JSVal -> JSM HTMLHeadingElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLHeadingElement
HTMLHeadingElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLHeadingElement where
  makeObject :: HTMLHeadingElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLHeadingElement -> JSVal)
-> HTMLHeadingElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLHeadingElement -> JSVal
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 :: HTMLHeadingElement -> JSM GType
typeGType HTMLHeadingElement
_ = JSM GType
gTypeHTMLHeadingElement
  {-# INLINE typeGType #-}

noHTMLHeadingElement :: Maybe HTMLHeadingElement
noHTMLHeadingElement :: Maybe HTMLHeadingElement
noHTMLHeadingElement = Maybe HTMLHeadingElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLHeadingElement #-}

gTypeHTMLHeadingElement :: JSM GType
gTypeHTMLHeadingElement :: JSM GType
gTypeHTMLHeadingElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLHeadingElement"

-- | Functions for this inteface are in "JSDOM.HTMLHtmlElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLHtmlElement Mozilla HTMLHtmlElement documentation>
newtype HTMLHtmlElement = HTMLHtmlElement { HTMLHtmlElement -> JSVal
unHTMLHtmlElement :: JSVal }

instance PToJSVal HTMLHtmlElement where
  pToJSVal :: HTMLHtmlElement -> JSVal
pToJSVal = HTMLHtmlElement -> JSVal
unHTMLHtmlElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLHtmlElement where
  pFromJSVal :: JSVal -> HTMLHtmlElement
pFromJSVal = JSVal -> HTMLHtmlElement
HTMLHtmlElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLHtmlElement where
  toJSVal :: HTMLHtmlElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLHtmlElement -> JSVal) -> HTMLHtmlElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLHtmlElement -> JSVal
unHTMLHtmlElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLHtmlElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLHtmlElement)
fromJSVal JSVal
v = (JSVal -> HTMLHtmlElement) -> Maybe JSVal -> Maybe HTMLHtmlElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLHtmlElement
HTMLHtmlElement (Maybe JSVal -> Maybe HTMLHtmlElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLHtmlElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLHtmlElement
fromJSValUnchecked = HTMLHtmlElement -> JSM HTMLHtmlElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLHtmlElement -> JSM HTMLHtmlElement)
-> (JSVal -> HTMLHtmlElement) -> JSVal -> JSM HTMLHtmlElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLHtmlElement
HTMLHtmlElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLHtmlElement where
  makeObject :: HTMLHtmlElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLHtmlElement -> JSVal) -> HTMLHtmlElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLHtmlElement -> JSVal
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 :: HTMLHtmlElement -> JSM GType
typeGType HTMLHtmlElement
_ = JSM GType
gTypeHTMLHtmlElement
  {-# INLINE typeGType #-}

noHTMLHtmlElement :: Maybe HTMLHtmlElement
noHTMLHtmlElement :: Maybe HTMLHtmlElement
noHTMLHtmlElement = Maybe HTMLHtmlElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLHtmlElement #-}

gTypeHTMLHtmlElement :: JSM GType
gTypeHTMLHtmlElement :: JSM GType
gTypeHTMLHtmlElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLHtmlElement"

-- | Functions for this inteface are in "JSDOM.HTMLHyperlinkElementUtils".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLHyperlinkElementUtils Mozilla HTMLHyperlinkElementUtils documentation>
newtype HTMLHyperlinkElementUtils = HTMLHyperlinkElementUtils { HTMLHyperlinkElementUtils -> JSVal
unHTMLHyperlinkElementUtils :: JSVal }

instance PToJSVal HTMLHyperlinkElementUtils where
  pToJSVal :: HTMLHyperlinkElementUtils -> JSVal
pToJSVal = HTMLHyperlinkElementUtils -> JSVal
unHTMLHyperlinkElementUtils
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLHyperlinkElementUtils where
  pFromJSVal :: JSVal -> HTMLHyperlinkElementUtils
pFromJSVal = JSVal -> HTMLHyperlinkElementUtils
HTMLHyperlinkElementUtils
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLHyperlinkElementUtils where
  toJSVal :: HTMLHyperlinkElementUtils -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLHyperlinkElementUtils -> JSVal)
-> HTMLHyperlinkElementUtils
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLHyperlinkElementUtils -> JSVal
unHTMLHyperlinkElementUtils
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLHyperlinkElementUtils where
  fromJSVal :: JSVal -> JSM (Maybe HTMLHyperlinkElementUtils)
fromJSVal JSVal
v = (JSVal -> HTMLHyperlinkElementUtils)
-> Maybe JSVal -> Maybe HTMLHyperlinkElementUtils
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLHyperlinkElementUtils
HTMLHyperlinkElementUtils (Maybe JSVal -> Maybe HTMLHyperlinkElementUtils)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLHyperlinkElementUtils)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLHyperlinkElementUtils
fromJSValUnchecked = HTMLHyperlinkElementUtils -> JSM HTMLHyperlinkElementUtils
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLHyperlinkElementUtils -> JSM HTMLHyperlinkElementUtils)
-> (JSVal -> HTMLHyperlinkElementUtils)
-> JSVal
-> JSM HTMLHyperlinkElementUtils
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLHyperlinkElementUtils
HTMLHyperlinkElementUtils
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLHyperlinkElementUtils where
  makeObject :: HTMLHyperlinkElementUtils -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLHyperlinkElementUtils -> JSVal)
-> HTMLHyperlinkElementUtils
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLHyperlinkElementUtils -> JSVal
unHTMLHyperlinkElementUtils

class (IsGObject o) => IsHTMLHyperlinkElementUtils o
toHTMLHyperlinkElementUtils :: IsHTMLHyperlinkElementUtils o => o -> HTMLHyperlinkElementUtils
toHTMLHyperlinkElementUtils :: forall o.
IsHTMLHyperlinkElementUtils o =>
o -> HTMLHyperlinkElementUtils
toHTMLHyperlinkElementUtils = JSVal -> HTMLHyperlinkElementUtils
HTMLHyperlinkElementUtils (JSVal -> HTMLHyperlinkElementUtils)
-> (o -> JSVal) -> o -> HTMLHyperlinkElementUtils
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsHTMLHyperlinkElementUtils HTMLHyperlinkElementUtils
instance IsGObject HTMLHyperlinkElementUtils where
  typeGType :: HTMLHyperlinkElementUtils -> JSM GType
typeGType HTMLHyperlinkElementUtils
_ = JSM GType
gTypeHTMLHyperlinkElementUtils
  {-# INLINE typeGType #-}

noHTMLHyperlinkElementUtils :: Maybe HTMLHyperlinkElementUtils
noHTMLHyperlinkElementUtils :: Maybe HTMLHyperlinkElementUtils
noHTMLHyperlinkElementUtils = Maybe HTMLHyperlinkElementUtils
forall a. Maybe a
Nothing
{-# INLINE noHTMLHyperlinkElementUtils #-}

gTypeHTMLHyperlinkElementUtils :: JSM GType
gTypeHTMLHyperlinkElementUtils :: JSM GType
gTypeHTMLHyperlinkElementUtils = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLHyperlinkElementUtils"

-- | Functions for this inteface are in "JSDOM.HTMLIFrameElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLIFrameElement Mozilla HTMLIFrameElement documentation>
newtype HTMLIFrameElement = HTMLIFrameElement { HTMLIFrameElement -> JSVal
unHTMLIFrameElement :: JSVal }

instance PToJSVal HTMLIFrameElement where
  pToJSVal :: HTMLIFrameElement -> JSVal
pToJSVal = HTMLIFrameElement -> JSVal
unHTMLIFrameElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLIFrameElement where
  pFromJSVal :: JSVal -> HTMLIFrameElement
pFromJSVal = JSVal -> HTMLIFrameElement
HTMLIFrameElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLIFrameElement where
  toJSVal :: HTMLIFrameElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLIFrameElement -> JSVal) -> HTMLIFrameElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLIFrameElement -> JSVal
unHTMLIFrameElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLIFrameElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLIFrameElement)
fromJSVal JSVal
v = (JSVal -> HTMLIFrameElement)
-> Maybe JSVal -> Maybe HTMLIFrameElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLIFrameElement
HTMLIFrameElement (Maybe JSVal -> Maybe HTMLIFrameElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLIFrameElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLIFrameElement
fromJSValUnchecked = HTMLIFrameElement -> JSM HTMLIFrameElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLIFrameElement -> JSM HTMLIFrameElement)
-> (JSVal -> HTMLIFrameElement) -> JSVal -> JSM HTMLIFrameElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLIFrameElement
HTMLIFrameElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLIFrameElement where
  makeObject :: HTMLIFrameElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLIFrameElement -> JSVal) -> HTMLIFrameElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLIFrameElement -> JSVal
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 :: HTMLIFrameElement -> JSM GType
typeGType HTMLIFrameElement
_ = JSM GType
gTypeHTMLIFrameElement
  {-# INLINE typeGType #-}

noHTMLIFrameElement :: Maybe HTMLIFrameElement
noHTMLIFrameElement :: Maybe HTMLIFrameElement
noHTMLIFrameElement = Maybe HTMLIFrameElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLIFrameElement #-}

gTypeHTMLIFrameElement :: JSM GType
gTypeHTMLIFrameElement :: JSM GType
gTypeHTMLIFrameElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLIFrameElement"

-- | Functions for this inteface are in "JSDOM.HTMLImageElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLImageElement Mozilla HTMLImageElement documentation>
newtype HTMLImageElement = HTMLImageElement { HTMLImageElement -> JSVal
unHTMLImageElement :: JSVal }

instance PToJSVal HTMLImageElement where
  pToJSVal :: HTMLImageElement -> JSVal
pToJSVal = HTMLImageElement -> JSVal
unHTMLImageElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLImageElement where
  pFromJSVal :: JSVal -> HTMLImageElement
pFromJSVal = JSVal -> HTMLImageElement
HTMLImageElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLImageElement where
  toJSVal :: HTMLImageElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLImageElement -> JSVal) -> HTMLImageElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLImageElement -> JSVal
unHTMLImageElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLImageElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLImageElement)
fromJSVal JSVal
v = (JSVal -> HTMLImageElement)
-> Maybe JSVal -> Maybe HTMLImageElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLImageElement
HTMLImageElement (Maybe JSVal -> Maybe HTMLImageElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLImageElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLImageElement
fromJSValUnchecked = HTMLImageElement -> JSM HTMLImageElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLImageElement -> JSM HTMLImageElement)
-> (JSVal -> HTMLImageElement) -> JSVal -> JSM HTMLImageElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLImageElement
HTMLImageElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLImageElement where
  makeObject :: HTMLImageElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLImageElement -> JSVal) -> HTMLImageElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLImageElement -> JSVal
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 :: HTMLImageElement -> JSM GType
typeGType HTMLImageElement
_ = JSM GType
gTypeHTMLImageElement
  {-# INLINE typeGType #-}

noHTMLImageElement :: Maybe HTMLImageElement
noHTMLImageElement :: Maybe HTMLImageElement
noHTMLImageElement = Maybe HTMLImageElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLImageElement #-}

gTypeHTMLImageElement :: JSM GType
gTypeHTMLImageElement :: JSM GType
gTypeHTMLImageElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLImageElement"

-- | Functions for this inteface are in "JSDOM.HTMLInputElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLInputElement Mozilla HTMLInputElement documentation>
newtype HTMLInputElement = HTMLInputElement { HTMLInputElement -> JSVal
unHTMLInputElement :: JSVal }

instance PToJSVal HTMLInputElement where
  pToJSVal :: HTMLInputElement -> JSVal
pToJSVal = HTMLInputElement -> JSVal
unHTMLInputElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLInputElement where
  pFromJSVal :: JSVal -> HTMLInputElement
pFromJSVal = JSVal -> HTMLInputElement
HTMLInputElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLInputElement where
  toJSVal :: HTMLInputElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLInputElement -> JSVal) -> HTMLInputElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLInputElement -> JSVal
unHTMLInputElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLInputElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLInputElement)
fromJSVal JSVal
v = (JSVal -> HTMLInputElement)
-> Maybe JSVal -> Maybe HTMLInputElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLInputElement
HTMLInputElement (Maybe JSVal -> Maybe HTMLInputElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLInputElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLInputElement
fromJSValUnchecked = HTMLInputElement -> JSM HTMLInputElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLInputElement -> JSM HTMLInputElement)
-> (JSVal -> HTMLInputElement) -> JSVal -> JSM HTMLInputElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLInputElement
HTMLInputElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLInputElement where
  makeObject :: HTMLInputElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLInputElement -> JSVal) -> HTMLInputElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLInputElement -> JSVal
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 :: HTMLInputElement -> JSM GType
typeGType HTMLInputElement
_ = JSM GType
gTypeHTMLInputElement
  {-# INLINE typeGType #-}

noHTMLInputElement :: Maybe HTMLInputElement
noHTMLInputElement :: Maybe HTMLInputElement
noHTMLInputElement = Maybe HTMLInputElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLInputElement #-}

gTypeHTMLInputElement :: JSM GType
gTypeHTMLInputElement :: JSM GType
gTypeHTMLInputElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLInputElement"

-- | Functions for this inteface are in "JSDOM.HTMLKeygenElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLKeygenElement Mozilla HTMLKeygenElement documentation>
newtype HTMLKeygenElement = HTMLKeygenElement { HTMLKeygenElement -> JSVal
unHTMLKeygenElement :: JSVal }

instance PToJSVal HTMLKeygenElement where
  pToJSVal :: HTMLKeygenElement -> JSVal
pToJSVal = HTMLKeygenElement -> JSVal
unHTMLKeygenElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLKeygenElement where
  pFromJSVal :: JSVal -> HTMLKeygenElement
pFromJSVal = JSVal -> HTMLKeygenElement
HTMLKeygenElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLKeygenElement where
  toJSVal :: HTMLKeygenElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLKeygenElement -> JSVal) -> HTMLKeygenElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLKeygenElement -> JSVal
unHTMLKeygenElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLKeygenElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLKeygenElement)
fromJSVal JSVal
v = (JSVal -> HTMLKeygenElement)
-> Maybe JSVal -> Maybe HTMLKeygenElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLKeygenElement
HTMLKeygenElement (Maybe JSVal -> Maybe HTMLKeygenElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLKeygenElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLKeygenElement
fromJSValUnchecked = HTMLKeygenElement -> JSM HTMLKeygenElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLKeygenElement -> JSM HTMLKeygenElement)
-> (JSVal -> HTMLKeygenElement) -> JSVal -> JSM HTMLKeygenElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLKeygenElement
HTMLKeygenElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLKeygenElement where
  makeObject :: HTMLKeygenElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLKeygenElement -> JSVal) -> HTMLKeygenElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLKeygenElement -> JSVal
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 :: HTMLKeygenElement -> JSM GType
typeGType HTMLKeygenElement
_ = JSM GType
gTypeHTMLKeygenElement
  {-# INLINE typeGType #-}

noHTMLKeygenElement :: Maybe HTMLKeygenElement
noHTMLKeygenElement :: Maybe HTMLKeygenElement
noHTMLKeygenElement = Maybe HTMLKeygenElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLKeygenElement #-}

gTypeHTMLKeygenElement :: JSM GType
gTypeHTMLKeygenElement :: JSM GType
gTypeHTMLKeygenElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLKeygenElement"

-- | Functions for this inteface are in "JSDOM.HTMLLIElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLLIElement Mozilla HTMLLIElement documentation>
newtype HTMLLIElement = HTMLLIElement { HTMLLIElement -> JSVal
unHTMLLIElement :: JSVal }

instance PToJSVal HTMLLIElement where
  pToJSVal :: HTMLLIElement -> JSVal
pToJSVal = HTMLLIElement -> JSVal
unHTMLLIElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLLIElement where
  pFromJSVal :: JSVal -> HTMLLIElement
pFromJSVal = JSVal -> HTMLLIElement
HTMLLIElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLLIElement where
  toJSVal :: HTMLLIElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLLIElement -> JSVal) -> HTMLLIElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLLIElement -> JSVal
unHTMLLIElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLLIElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLLIElement)
fromJSVal JSVal
v = (JSVal -> HTMLLIElement) -> Maybe JSVal -> Maybe HTMLLIElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLLIElement
HTMLLIElement (Maybe JSVal -> Maybe HTMLLIElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLLIElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLLIElement
fromJSValUnchecked = HTMLLIElement -> JSM HTMLLIElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLLIElement -> JSM HTMLLIElement)
-> (JSVal -> HTMLLIElement) -> JSVal -> JSM HTMLLIElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLLIElement
HTMLLIElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLLIElement where
  makeObject :: HTMLLIElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLLIElement -> JSVal) -> HTMLLIElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLLIElement -> JSVal
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 :: HTMLLIElement -> JSM GType
typeGType HTMLLIElement
_ = JSM GType
gTypeHTMLLIElement
  {-# INLINE typeGType #-}

noHTMLLIElement :: Maybe HTMLLIElement
noHTMLLIElement :: Maybe HTMLLIElement
noHTMLLIElement = Maybe HTMLLIElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLLIElement #-}

gTypeHTMLLIElement :: JSM GType
gTypeHTMLLIElement :: JSM GType
gTypeHTMLLIElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLLIElement"

-- | Functions for this inteface are in "JSDOM.HTMLLabelElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLLabelElement Mozilla HTMLLabelElement documentation>
newtype HTMLLabelElement = HTMLLabelElement { HTMLLabelElement -> JSVal
unHTMLLabelElement :: JSVal }

instance PToJSVal HTMLLabelElement where
  pToJSVal :: HTMLLabelElement -> JSVal
pToJSVal = HTMLLabelElement -> JSVal
unHTMLLabelElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLLabelElement where
  pFromJSVal :: JSVal -> HTMLLabelElement
pFromJSVal = JSVal -> HTMLLabelElement
HTMLLabelElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLLabelElement where
  toJSVal :: HTMLLabelElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLLabelElement -> JSVal) -> HTMLLabelElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLLabelElement -> JSVal
unHTMLLabelElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLLabelElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLLabelElement)
fromJSVal JSVal
v = (JSVal -> HTMLLabelElement)
-> Maybe JSVal -> Maybe HTMLLabelElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLLabelElement
HTMLLabelElement (Maybe JSVal -> Maybe HTMLLabelElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLLabelElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLLabelElement
fromJSValUnchecked = HTMLLabelElement -> JSM HTMLLabelElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLLabelElement -> JSM HTMLLabelElement)
-> (JSVal -> HTMLLabelElement) -> JSVal -> JSM HTMLLabelElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLLabelElement
HTMLLabelElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLLabelElement where
  makeObject :: HTMLLabelElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLLabelElement -> JSVal) -> HTMLLabelElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLLabelElement -> JSVal
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 :: HTMLLabelElement -> JSM GType
typeGType HTMLLabelElement
_ = JSM GType
gTypeHTMLLabelElement
  {-# INLINE typeGType #-}

noHTMLLabelElement :: Maybe HTMLLabelElement
noHTMLLabelElement :: Maybe HTMLLabelElement
noHTMLLabelElement = Maybe HTMLLabelElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLLabelElement #-}

gTypeHTMLLabelElement :: JSM GType
gTypeHTMLLabelElement :: JSM GType
gTypeHTMLLabelElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLLabelElement"

-- | Functions for this inteface are in "JSDOM.HTMLLegendElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLLegendElement Mozilla HTMLLegendElement documentation>
newtype HTMLLegendElement = HTMLLegendElement { HTMLLegendElement -> JSVal
unHTMLLegendElement :: JSVal }

instance PToJSVal HTMLLegendElement where
  pToJSVal :: HTMLLegendElement -> JSVal
pToJSVal = HTMLLegendElement -> JSVal
unHTMLLegendElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLLegendElement where
  pFromJSVal :: JSVal -> HTMLLegendElement
pFromJSVal = JSVal -> HTMLLegendElement
HTMLLegendElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLLegendElement where
  toJSVal :: HTMLLegendElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLLegendElement -> JSVal) -> HTMLLegendElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLLegendElement -> JSVal
unHTMLLegendElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLLegendElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLLegendElement)
fromJSVal JSVal
v = (JSVal -> HTMLLegendElement)
-> Maybe JSVal -> Maybe HTMLLegendElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLLegendElement
HTMLLegendElement (Maybe JSVal -> Maybe HTMLLegendElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLLegendElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLLegendElement
fromJSValUnchecked = HTMLLegendElement -> JSM HTMLLegendElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLLegendElement -> JSM HTMLLegendElement)
-> (JSVal -> HTMLLegendElement) -> JSVal -> JSM HTMLLegendElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLLegendElement
HTMLLegendElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLLegendElement where
  makeObject :: HTMLLegendElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLLegendElement -> JSVal) -> HTMLLegendElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLLegendElement -> JSVal
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 :: HTMLLegendElement -> JSM GType
typeGType HTMLLegendElement
_ = JSM GType
gTypeHTMLLegendElement
  {-# INLINE typeGType #-}

noHTMLLegendElement :: Maybe HTMLLegendElement
noHTMLLegendElement :: Maybe HTMLLegendElement
noHTMLLegendElement = Maybe HTMLLegendElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLLegendElement #-}

gTypeHTMLLegendElement :: JSM GType
gTypeHTMLLegendElement :: JSM GType
gTypeHTMLLegendElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLLegendElement"

-- | Functions for this inteface are in "JSDOM.HTMLLinkElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLLinkElement Mozilla HTMLLinkElement documentation>
newtype HTMLLinkElement = HTMLLinkElement { HTMLLinkElement -> JSVal
unHTMLLinkElement :: JSVal }

instance PToJSVal HTMLLinkElement where
  pToJSVal :: HTMLLinkElement -> JSVal
pToJSVal = HTMLLinkElement -> JSVal
unHTMLLinkElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLLinkElement where
  pFromJSVal :: JSVal -> HTMLLinkElement
pFromJSVal = JSVal -> HTMLLinkElement
HTMLLinkElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLLinkElement where
  toJSVal :: HTMLLinkElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLLinkElement -> JSVal) -> HTMLLinkElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLLinkElement -> JSVal
unHTMLLinkElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLLinkElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLLinkElement)
fromJSVal JSVal
v = (JSVal -> HTMLLinkElement) -> Maybe JSVal -> Maybe HTMLLinkElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLLinkElement
HTMLLinkElement (Maybe JSVal -> Maybe HTMLLinkElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLLinkElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLLinkElement
fromJSValUnchecked = HTMLLinkElement -> JSM HTMLLinkElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLLinkElement -> JSM HTMLLinkElement)
-> (JSVal -> HTMLLinkElement) -> JSVal -> JSM HTMLLinkElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLLinkElement
HTMLLinkElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLLinkElement where
  makeObject :: HTMLLinkElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLLinkElement -> JSVal) -> HTMLLinkElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLLinkElement -> JSVal
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 :: HTMLLinkElement -> JSM GType
typeGType HTMLLinkElement
_ = JSM GType
gTypeHTMLLinkElement
  {-# INLINE typeGType #-}

noHTMLLinkElement :: Maybe HTMLLinkElement
noHTMLLinkElement :: Maybe HTMLLinkElement
noHTMLLinkElement = Maybe HTMLLinkElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLLinkElement #-}

gTypeHTMLLinkElement :: JSM GType
gTypeHTMLLinkElement :: JSM GType
gTypeHTMLLinkElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLLinkElement"

-- | Functions for this inteface are in "JSDOM.HTMLMapElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLMapElement Mozilla HTMLMapElement documentation>
newtype HTMLMapElement = HTMLMapElement { HTMLMapElement -> JSVal
unHTMLMapElement :: JSVal }

instance PToJSVal HTMLMapElement where
  pToJSVal :: HTMLMapElement -> JSVal
pToJSVal = HTMLMapElement -> JSVal
unHTMLMapElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLMapElement where
  pFromJSVal :: JSVal -> HTMLMapElement
pFromJSVal = JSVal -> HTMLMapElement
HTMLMapElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLMapElement where
  toJSVal :: HTMLMapElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLMapElement -> JSVal) -> HTMLMapElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMapElement -> JSVal
unHTMLMapElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLMapElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLMapElement)
fromJSVal JSVal
v = (JSVal -> HTMLMapElement) -> Maybe JSVal -> Maybe HTMLMapElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLMapElement
HTMLMapElement (Maybe JSVal -> Maybe HTMLMapElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLMapElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLMapElement
fromJSValUnchecked = HTMLMapElement -> JSM HTMLMapElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMapElement -> JSM HTMLMapElement)
-> (JSVal -> HTMLMapElement) -> JSVal -> JSM HTMLMapElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLMapElement
HTMLMapElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLMapElement where
  makeObject :: HTMLMapElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLMapElement -> JSVal) -> HTMLMapElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMapElement -> JSVal
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 :: HTMLMapElement -> JSM GType
typeGType HTMLMapElement
_ = JSM GType
gTypeHTMLMapElement
  {-# INLINE typeGType #-}

noHTMLMapElement :: Maybe HTMLMapElement
noHTMLMapElement :: Maybe HTMLMapElement
noHTMLMapElement = Maybe HTMLMapElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLMapElement #-}

gTypeHTMLMapElement :: JSM GType
gTypeHTMLMapElement :: JSM GType
gTypeHTMLMapElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLMapElement"

-- | Functions for this inteface are in "JSDOM.HTMLMarqueeElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLMarqueeElement Mozilla HTMLMarqueeElement documentation>
newtype HTMLMarqueeElement = HTMLMarqueeElement { HTMLMarqueeElement -> JSVal
unHTMLMarqueeElement :: JSVal }

instance PToJSVal HTMLMarqueeElement where
  pToJSVal :: HTMLMarqueeElement -> JSVal
pToJSVal = HTMLMarqueeElement -> JSVal
unHTMLMarqueeElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLMarqueeElement where
  pFromJSVal :: JSVal -> HTMLMarqueeElement
pFromJSVal = JSVal -> HTMLMarqueeElement
HTMLMarqueeElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLMarqueeElement where
  toJSVal :: HTMLMarqueeElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLMarqueeElement -> JSVal) -> HTMLMarqueeElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMarqueeElement -> JSVal
unHTMLMarqueeElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLMarqueeElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLMarqueeElement)
fromJSVal JSVal
v = (JSVal -> HTMLMarqueeElement)
-> Maybe JSVal -> Maybe HTMLMarqueeElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLMarqueeElement
HTMLMarqueeElement (Maybe JSVal -> Maybe HTMLMarqueeElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLMarqueeElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLMarqueeElement
fromJSValUnchecked = HTMLMarqueeElement -> JSM HTMLMarqueeElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMarqueeElement -> JSM HTMLMarqueeElement)
-> (JSVal -> HTMLMarqueeElement) -> JSVal -> JSM HTMLMarqueeElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLMarqueeElement
HTMLMarqueeElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLMarqueeElement where
  makeObject :: HTMLMarqueeElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLMarqueeElement -> JSVal)
-> HTMLMarqueeElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMarqueeElement -> JSVal
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 :: HTMLMarqueeElement -> JSM GType
typeGType HTMLMarqueeElement
_ = JSM GType
gTypeHTMLMarqueeElement
  {-# INLINE typeGType #-}

noHTMLMarqueeElement :: Maybe HTMLMarqueeElement
noHTMLMarqueeElement :: Maybe HTMLMarqueeElement
noHTMLMarqueeElement = Maybe HTMLMarqueeElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLMarqueeElement #-}

gTypeHTMLMarqueeElement :: JSM GType
gTypeHTMLMarqueeElement :: JSM GType
gTypeHTMLMarqueeElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLMarqueeElement"

-- | Functions for this inteface are in "JSDOM.HTMLMediaElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLMediaElement Mozilla HTMLMediaElement documentation>
newtype HTMLMediaElement = HTMLMediaElement { HTMLMediaElement -> JSVal
unHTMLMediaElement :: JSVal }

instance PToJSVal HTMLMediaElement where
  pToJSVal :: HTMLMediaElement -> JSVal
pToJSVal = HTMLMediaElement -> JSVal
unHTMLMediaElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLMediaElement where
  pFromJSVal :: JSVal -> HTMLMediaElement
pFromJSVal = JSVal -> HTMLMediaElement
HTMLMediaElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLMediaElement where
  toJSVal :: HTMLMediaElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLMediaElement -> JSVal) -> HTMLMediaElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMediaElement -> JSVal
unHTMLMediaElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLMediaElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLMediaElement)
fromJSVal JSVal
v = (JSVal -> HTMLMediaElement)
-> Maybe JSVal -> Maybe HTMLMediaElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLMediaElement
HTMLMediaElement (Maybe JSVal -> Maybe HTMLMediaElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLMediaElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLMediaElement
fromJSValUnchecked = HTMLMediaElement -> JSM HTMLMediaElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMediaElement -> JSM HTMLMediaElement)
-> (JSVal -> HTMLMediaElement) -> JSVal -> JSM HTMLMediaElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLMediaElement
HTMLMediaElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLMediaElement where
  makeObject :: HTMLMediaElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLMediaElement -> JSVal) -> HTMLMediaElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMediaElement -> JSVal
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 :: forall o. IsHTMLMediaElement o => o -> HTMLMediaElement
toHTMLMediaElement = JSVal -> HTMLMediaElement
HTMLMediaElement (JSVal -> HTMLMediaElement)
-> (o -> JSVal) -> o -> HTMLMediaElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: HTMLMediaElement -> JSM GType
typeGType HTMLMediaElement
_ = JSM GType
gTypeHTMLMediaElement
  {-# INLINE typeGType #-}

noHTMLMediaElement :: Maybe HTMLMediaElement
noHTMLMediaElement :: Maybe HTMLMediaElement
noHTMLMediaElement = Maybe HTMLMediaElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLMediaElement #-}

gTypeHTMLMediaElement :: JSM GType
gTypeHTMLMediaElement :: JSM GType
gTypeHTMLMediaElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLMediaElement"

-- | Functions for this inteface are in "JSDOM.HTMLMenuElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLMenuElement Mozilla HTMLMenuElement documentation>
newtype HTMLMenuElement = HTMLMenuElement { HTMLMenuElement -> JSVal
unHTMLMenuElement :: JSVal }

instance PToJSVal HTMLMenuElement where
  pToJSVal :: HTMLMenuElement -> JSVal
pToJSVal = HTMLMenuElement -> JSVal
unHTMLMenuElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLMenuElement where
  pFromJSVal :: JSVal -> HTMLMenuElement
pFromJSVal = JSVal -> HTMLMenuElement
HTMLMenuElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLMenuElement where
  toJSVal :: HTMLMenuElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLMenuElement -> JSVal) -> HTMLMenuElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMenuElement -> JSVal
unHTMLMenuElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLMenuElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLMenuElement)
fromJSVal JSVal
v = (JSVal -> HTMLMenuElement) -> Maybe JSVal -> Maybe HTMLMenuElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLMenuElement
HTMLMenuElement (Maybe JSVal -> Maybe HTMLMenuElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLMenuElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLMenuElement
fromJSValUnchecked = HTMLMenuElement -> JSM HTMLMenuElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMenuElement -> JSM HTMLMenuElement)
-> (JSVal -> HTMLMenuElement) -> JSVal -> JSM HTMLMenuElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLMenuElement
HTMLMenuElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLMenuElement where
  makeObject :: HTMLMenuElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLMenuElement -> JSVal) -> HTMLMenuElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMenuElement -> JSVal
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 :: HTMLMenuElement -> JSM GType
typeGType HTMLMenuElement
_ = JSM GType
gTypeHTMLMenuElement
  {-# INLINE typeGType #-}

noHTMLMenuElement :: Maybe HTMLMenuElement
noHTMLMenuElement :: Maybe HTMLMenuElement
noHTMLMenuElement = Maybe HTMLMenuElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLMenuElement #-}

gTypeHTMLMenuElement :: JSM GType
gTypeHTMLMenuElement :: JSM GType
gTypeHTMLMenuElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLMenuElement"

-- | Functions for this inteface are in "JSDOM.HTMLMetaElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLMetaElement Mozilla HTMLMetaElement documentation>
newtype HTMLMetaElement = HTMLMetaElement { HTMLMetaElement -> JSVal
unHTMLMetaElement :: JSVal }

instance PToJSVal HTMLMetaElement where
  pToJSVal :: HTMLMetaElement -> JSVal
pToJSVal = HTMLMetaElement -> JSVal
unHTMLMetaElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLMetaElement where
  pFromJSVal :: JSVal -> HTMLMetaElement
pFromJSVal = JSVal -> HTMLMetaElement
HTMLMetaElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLMetaElement where
  toJSVal :: HTMLMetaElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLMetaElement -> JSVal) -> HTMLMetaElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMetaElement -> JSVal
unHTMLMetaElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLMetaElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLMetaElement)
fromJSVal JSVal
v = (JSVal -> HTMLMetaElement) -> Maybe JSVal -> Maybe HTMLMetaElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLMetaElement
HTMLMetaElement (Maybe JSVal -> Maybe HTMLMetaElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLMetaElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLMetaElement
fromJSValUnchecked = HTMLMetaElement -> JSM HTMLMetaElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMetaElement -> JSM HTMLMetaElement)
-> (JSVal -> HTMLMetaElement) -> JSVal -> JSM HTMLMetaElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLMetaElement
HTMLMetaElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLMetaElement where
  makeObject :: HTMLMetaElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLMetaElement -> JSVal) -> HTMLMetaElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMetaElement -> JSVal
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 :: HTMLMetaElement -> JSM GType
typeGType HTMLMetaElement
_ = JSM GType
gTypeHTMLMetaElement
  {-# INLINE typeGType #-}

noHTMLMetaElement :: Maybe HTMLMetaElement
noHTMLMetaElement :: Maybe HTMLMetaElement
noHTMLMetaElement = Maybe HTMLMetaElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLMetaElement #-}

gTypeHTMLMetaElement :: JSM GType
gTypeHTMLMetaElement :: JSM GType
gTypeHTMLMetaElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLMetaElement"

-- | Functions for this inteface are in "JSDOM.HTMLMeterElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLMeterElement Mozilla HTMLMeterElement documentation>
newtype HTMLMeterElement = HTMLMeterElement { HTMLMeterElement -> JSVal
unHTMLMeterElement :: JSVal }

instance PToJSVal HTMLMeterElement where
  pToJSVal :: HTMLMeterElement -> JSVal
pToJSVal = HTMLMeterElement -> JSVal
unHTMLMeterElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLMeterElement where
  pFromJSVal :: JSVal -> HTMLMeterElement
pFromJSVal = JSVal -> HTMLMeterElement
HTMLMeterElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLMeterElement where
  toJSVal :: HTMLMeterElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLMeterElement -> JSVal) -> HTMLMeterElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMeterElement -> JSVal
unHTMLMeterElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLMeterElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLMeterElement)
fromJSVal JSVal
v = (JSVal -> HTMLMeterElement)
-> Maybe JSVal -> Maybe HTMLMeterElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLMeterElement
HTMLMeterElement (Maybe JSVal -> Maybe HTMLMeterElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLMeterElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLMeterElement
fromJSValUnchecked = HTMLMeterElement -> JSM HTMLMeterElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLMeterElement -> JSM HTMLMeterElement)
-> (JSVal -> HTMLMeterElement) -> JSVal -> JSM HTMLMeterElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLMeterElement
HTMLMeterElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLMeterElement where
  makeObject :: HTMLMeterElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLMeterElement -> JSVal) -> HTMLMeterElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLMeterElement -> JSVal
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 :: HTMLMeterElement -> JSM GType
typeGType HTMLMeterElement
_ = JSM GType
gTypeHTMLMeterElement
  {-# INLINE typeGType #-}

noHTMLMeterElement :: Maybe HTMLMeterElement
noHTMLMeterElement :: Maybe HTMLMeterElement
noHTMLMeterElement = Maybe HTMLMeterElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLMeterElement #-}

gTypeHTMLMeterElement :: JSM GType
gTypeHTMLMeterElement :: JSM GType
gTypeHTMLMeterElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLMeterElement"

-- | Functions for this inteface are in "JSDOM.HTMLModElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLModElement Mozilla HTMLModElement documentation>
newtype HTMLModElement = HTMLModElement { HTMLModElement -> JSVal
unHTMLModElement :: JSVal }

instance PToJSVal HTMLModElement where
  pToJSVal :: HTMLModElement -> JSVal
pToJSVal = HTMLModElement -> JSVal
unHTMLModElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLModElement where
  pFromJSVal :: JSVal -> HTMLModElement
pFromJSVal = JSVal -> HTMLModElement
HTMLModElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLModElement where
  toJSVal :: HTMLModElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLModElement -> JSVal) -> HTMLModElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLModElement -> JSVal
unHTMLModElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLModElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLModElement)
fromJSVal JSVal
v = (JSVal -> HTMLModElement) -> Maybe JSVal -> Maybe HTMLModElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLModElement
HTMLModElement (Maybe JSVal -> Maybe HTMLModElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLModElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLModElement
fromJSValUnchecked = HTMLModElement -> JSM HTMLModElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLModElement -> JSM HTMLModElement)
-> (JSVal -> HTMLModElement) -> JSVal -> JSM HTMLModElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLModElement
HTMLModElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLModElement where
  makeObject :: HTMLModElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLModElement -> JSVal) -> HTMLModElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLModElement -> JSVal
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 :: HTMLModElement -> JSM GType
typeGType HTMLModElement
_ = JSM GType
gTypeHTMLModElement
  {-# INLINE typeGType #-}

noHTMLModElement :: Maybe HTMLModElement
noHTMLModElement :: Maybe HTMLModElement
noHTMLModElement = Maybe HTMLModElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLModElement #-}

gTypeHTMLModElement :: JSM GType
gTypeHTMLModElement :: JSM GType
gTypeHTMLModElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLModElement"

-- | Functions for this inteface are in "JSDOM.HTMLOListElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLOListElement Mozilla HTMLOListElement documentation>
newtype HTMLOListElement = HTMLOListElement { HTMLOListElement -> JSVal
unHTMLOListElement :: JSVal }

instance PToJSVal HTMLOListElement where
  pToJSVal :: HTMLOListElement -> JSVal
pToJSVal = HTMLOListElement -> JSVal
unHTMLOListElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLOListElement where
  pFromJSVal :: JSVal -> HTMLOListElement
pFromJSVal = JSVal -> HTMLOListElement
HTMLOListElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLOListElement where
  toJSVal :: HTMLOListElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLOListElement -> JSVal) -> HTMLOListElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOListElement -> JSVal
unHTMLOListElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLOListElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLOListElement)
fromJSVal JSVal
v = (JSVal -> HTMLOListElement)
-> Maybe JSVal -> Maybe HTMLOListElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLOListElement
HTMLOListElement (Maybe JSVal -> Maybe HTMLOListElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLOListElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLOListElement
fromJSValUnchecked = HTMLOListElement -> JSM HTMLOListElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLOListElement -> JSM HTMLOListElement)
-> (JSVal -> HTMLOListElement) -> JSVal -> JSM HTMLOListElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLOListElement
HTMLOListElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLOListElement where
  makeObject :: HTMLOListElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLOListElement -> JSVal) -> HTMLOListElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOListElement -> JSVal
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 :: HTMLOListElement -> JSM GType
typeGType HTMLOListElement
_ = JSM GType
gTypeHTMLOListElement
  {-# INLINE typeGType #-}

noHTMLOListElement :: Maybe HTMLOListElement
noHTMLOListElement :: Maybe HTMLOListElement
noHTMLOListElement = Maybe HTMLOListElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLOListElement #-}

gTypeHTMLOListElement :: JSM GType
gTypeHTMLOListElement :: JSM GType
gTypeHTMLOListElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLOListElement"

-- | Functions for this inteface are in "JSDOM.HTMLObjectElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLObjectElement Mozilla HTMLObjectElement documentation>
newtype HTMLObjectElement = HTMLObjectElement { HTMLObjectElement -> JSVal
unHTMLObjectElement :: JSVal }

instance PToJSVal HTMLObjectElement where
  pToJSVal :: HTMLObjectElement -> JSVal
pToJSVal = HTMLObjectElement -> JSVal
unHTMLObjectElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLObjectElement where
  pFromJSVal :: JSVal -> HTMLObjectElement
pFromJSVal = JSVal -> HTMLObjectElement
HTMLObjectElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLObjectElement where
  toJSVal :: HTMLObjectElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLObjectElement -> JSVal) -> HTMLObjectElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLObjectElement -> JSVal
unHTMLObjectElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLObjectElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLObjectElement)
fromJSVal JSVal
v = (JSVal -> HTMLObjectElement)
-> Maybe JSVal -> Maybe HTMLObjectElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLObjectElement
HTMLObjectElement (Maybe JSVal -> Maybe HTMLObjectElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLObjectElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLObjectElement
fromJSValUnchecked = HTMLObjectElement -> JSM HTMLObjectElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLObjectElement -> JSM HTMLObjectElement)
-> (JSVal -> HTMLObjectElement) -> JSVal -> JSM HTMLObjectElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLObjectElement
HTMLObjectElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLObjectElement where
  makeObject :: HTMLObjectElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLObjectElement -> JSVal) -> HTMLObjectElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLObjectElement -> JSVal
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 :: HTMLObjectElement -> JSM GType
typeGType HTMLObjectElement
_ = JSM GType
gTypeHTMLObjectElement
  {-# INLINE typeGType #-}

noHTMLObjectElement :: Maybe HTMLObjectElement
noHTMLObjectElement :: Maybe HTMLObjectElement
noHTMLObjectElement = Maybe HTMLObjectElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLObjectElement #-}

gTypeHTMLObjectElement :: JSM GType
gTypeHTMLObjectElement :: JSM GType
gTypeHTMLObjectElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLObjectElement"

-- | Functions for this inteface are in "JSDOM.HTMLOptGroupElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLOptGroupElement Mozilla HTMLOptGroupElement documentation>
newtype HTMLOptGroupElement = HTMLOptGroupElement { HTMLOptGroupElement -> JSVal
unHTMLOptGroupElement :: JSVal }

instance PToJSVal HTMLOptGroupElement where
  pToJSVal :: HTMLOptGroupElement -> JSVal
pToJSVal = HTMLOptGroupElement -> JSVal
unHTMLOptGroupElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLOptGroupElement where
  pFromJSVal :: JSVal -> HTMLOptGroupElement
pFromJSVal = JSVal -> HTMLOptGroupElement
HTMLOptGroupElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLOptGroupElement where
  toJSVal :: HTMLOptGroupElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLOptGroupElement -> JSVal)
-> HTMLOptGroupElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOptGroupElement -> JSVal
unHTMLOptGroupElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLOptGroupElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLOptGroupElement)
fromJSVal JSVal
v = (JSVal -> HTMLOptGroupElement)
-> Maybe JSVal -> Maybe HTMLOptGroupElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLOptGroupElement
HTMLOptGroupElement (Maybe JSVal -> Maybe HTMLOptGroupElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLOptGroupElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLOptGroupElement
fromJSValUnchecked = HTMLOptGroupElement -> JSM HTMLOptGroupElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLOptGroupElement -> JSM HTMLOptGroupElement)
-> (JSVal -> HTMLOptGroupElement)
-> JSVal
-> JSM HTMLOptGroupElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLOptGroupElement
HTMLOptGroupElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLOptGroupElement where
  makeObject :: HTMLOptGroupElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLOptGroupElement -> JSVal)
-> HTMLOptGroupElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOptGroupElement -> JSVal
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 :: HTMLOptGroupElement -> JSM GType
typeGType HTMLOptGroupElement
_ = JSM GType
gTypeHTMLOptGroupElement
  {-# INLINE typeGType #-}

noHTMLOptGroupElement :: Maybe HTMLOptGroupElement
noHTMLOptGroupElement :: Maybe HTMLOptGroupElement
noHTMLOptGroupElement = Maybe HTMLOptGroupElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLOptGroupElement #-}

gTypeHTMLOptGroupElement :: JSM GType
gTypeHTMLOptGroupElement :: JSM GType
gTypeHTMLOptGroupElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLOptGroupElement"

-- | Functions for this inteface are in "JSDOM.HTMLOptionElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLOptionElement Mozilla HTMLOptionElement documentation>
newtype HTMLOptionElement = HTMLOptionElement { HTMLOptionElement -> JSVal
unHTMLOptionElement :: JSVal }

instance PToJSVal HTMLOptionElement where
  pToJSVal :: HTMLOptionElement -> JSVal
pToJSVal = HTMLOptionElement -> JSVal
unHTMLOptionElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLOptionElement where
  pFromJSVal :: JSVal -> HTMLOptionElement
pFromJSVal = JSVal -> HTMLOptionElement
HTMLOptionElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLOptionElement where
  toJSVal :: HTMLOptionElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLOptionElement -> JSVal) -> HTMLOptionElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOptionElement -> JSVal
unHTMLOptionElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLOptionElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLOptionElement)
fromJSVal JSVal
v = (JSVal -> HTMLOptionElement)
-> Maybe JSVal -> Maybe HTMLOptionElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLOptionElement
HTMLOptionElement (Maybe JSVal -> Maybe HTMLOptionElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLOptionElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLOptionElement
fromJSValUnchecked = HTMLOptionElement -> JSM HTMLOptionElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLOptionElement -> JSM HTMLOptionElement)
-> (JSVal -> HTMLOptionElement) -> JSVal -> JSM HTMLOptionElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLOptionElement
HTMLOptionElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLOptionElement where
  makeObject :: HTMLOptionElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLOptionElement -> JSVal) -> HTMLOptionElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOptionElement -> JSVal
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 :: HTMLOptionElement -> JSM GType
typeGType HTMLOptionElement
_ = JSM GType
gTypeHTMLOptionElement
  {-# INLINE typeGType #-}

noHTMLOptionElement :: Maybe HTMLOptionElement
noHTMLOptionElement :: Maybe HTMLOptionElement
noHTMLOptionElement = Maybe HTMLOptionElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLOptionElement #-}

gTypeHTMLOptionElement :: JSM GType
gTypeHTMLOptionElement :: JSM GType
gTypeHTMLOptionElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLOptionElement"

-- | Functions for this inteface are in "JSDOM.HTMLOptionsCollection".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLCollection"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLOptionsCollection Mozilla HTMLOptionsCollection documentation>
newtype HTMLOptionsCollection = HTMLOptionsCollection { HTMLOptionsCollection -> JSVal
unHTMLOptionsCollection :: JSVal }

instance PToJSVal HTMLOptionsCollection where
  pToJSVal :: HTMLOptionsCollection -> JSVal
pToJSVal = HTMLOptionsCollection -> JSVal
unHTMLOptionsCollection
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLOptionsCollection where
  pFromJSVal :: JSVal -> HTMLOptionsCollection
pFromJSVal = JSVal -> HTMLOptionsCollection
HTMLOptionsCollection
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLOptionsCollection where
  toJSVal :: HTMLOptionsCollection -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLOptionsCollection -> JSVal)
-> HTMLOptionsCollection
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOptionsCollection -> JSVal
unHTMLOptionsCollection
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLOptionsCollection where
  fromJSVal :: JSVal -> JSM (Maybe HTMLOptionsCollection)
fromJSVal JSVal
v = (JSVal -> HTMLOptionsCollection)
-> Maybe JSVal -> Maybe HTMLOptionsCollection
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLOptionsCollection
HTMLOptionsCollection (Maybe JSVal -> Maybe HTMLOptionsCollection)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLOptionsCollection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLOptionsCollection
fromJSValUnchecked = HTMLOptionsCollection -> JSM HTMLOptionsCollection
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLOptionsCollection -> JSM HTMLOptionsCollection)
-> (JSVal -> HTMLOptionsCollection)
-> JSVal
-> JSM HTMLOptionsCollection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLOptionsCollection
HTMLOptionsCollection
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLOptionsCollection where
  makeObject :: HTMLOptionsCollection -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLOptionsCollection -> JSVal)
-> HTMLOptionsCollection
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOptionsCollection -> JSVal
unHTMLOptionsCollection

instance IsHTMLCollection HTMLOptionsCollection
instance IsGObject HTMLOptionsCollection where
  typeGType :: HTMLOptionsCollection -> JSM GType
typeGType HTMLOptionsCollection
_ = JSM GType
gTypeHTMLOptionsCollection
  {-# INLINE typeGType #-}

noHTMLOptionsCollection :: Maybe HTMLOptionsCollection
noHTMLOptionsCollection :: Maybe HTMLOptionsCollection
noHTMLOptionsCollection = Maybe HTMLOptionsCollection
forall a. Maybe a
Nothing
{-# INLINE noHTMLOptionsCollection #-}

gTypeHTMLOptionsCollection :: JSM GType
gTypeHTMLOptionsCollection :: JSM GType
gTypeHTMLOptionsCollection = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLOptionsCollection"

-- | Functions for this inteface are in "JSDOM.HTMLOutputElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLOutputElement Mozilla HTMLOutputElement documentation>
newtype HTMLOutputElement = HTMLOutputElement { HTMLOutputElement -> JSVal
unHTMLOutputElement :: JSVal }

instance PToJSVal HTMLOutputElement where
  pToJSVal :: HTMLOutputElement -> JSVal
pToJSVal = HTMLOutputElement -> JSVal
unHTMLOutputElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLOutputElement where
  pFromJSVal :: JSVal -> HTMLOutputElement
pFromJSVal = JSVal -> HTMLOutputElement
HTMLOutputElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLOutputElement where
  toJSVal :: HTMLOutputElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLOutputElement -> JSVal) -> HTMLOutputElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOutputElement -> JSVal
unHTMLOutputElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLOutputElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLOutputElement)
fromJSVal JSVal
v = (JSVal -> HTMLOutputElement)
-> Maybe JSVal -> Maybe HTMLOutputElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLOutputElement
HTMLOutputElement (Maybe JSVal -> Maybe HTMLOutputElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLOutputElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLOutputElement
fromJSValUnchecked = HTMLOutputElement -> JSM HTMLOutputElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLOutputElement -> JSM HTMLOutputElement)
-> (JSVal -> HTMLOutputElement) -> JSVal -> JSM HTMLOutputElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLOutputElement
HTMLOutputElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLOutputElement where
  makeObject :: HTMLOutputElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLOutputElement -> JSVal) -> HTMLOutputElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLOutputElement -> JSVal
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 :: HTMLOutputElement -> JSM GType
typeGType HTMLOutputElement
_ = JSM GType
gTypeHTMLOutputElement
  {-# INLINE typeGType #-}

noHTMLOutputElement :: Maybe HTMLOutputElement
noHTMLOutputElement :: Maybe HTMLOutputElement
noHTMLOutputElement = Maybe HTMLOutputElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLOutputElement #-}

gTypeHTMLOutputElement :: JSM GType
gTypeHTMLOutputElement :: JSM GType
gTypeHTMLOutputElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLOutputElement"

-- | Functions for this inteface are in "JSDOM.HTMLParagraphElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLParagraphElement Mozilla HTMLParagraphElement documentation>
newtype HTMLParagraphElement = HTMLParagraphElement { HTMLParagraphElement -> JSVal
unHTMLParagraphElement :: JSVal }

instance PToJSVal HTMLParagraphElement where
  pToJSVal :: HTMLParagraphElement -> JSVal
pToJSVal = HTMLParagraphElement -> JSVal
unHTMLParagraphElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLParagraphElement where
  pFromJSVal :: JSVal -> HTMLParagraphElement
pFromJSVal = JSVal -> HTMLParagraphElement
HTMLParagraphElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLParagraphElement where
  toJSVal :: HTMLParagraphElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLParagraphElement -> JSVal)
-> HTMLParagraphElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLParagraphElement -> JSVal
unHTMLParagraphElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLParagraphElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLParagraphElement)
fromJSVal JSVal
v = (JSVal -> HTMLParagraphElement)
-> Maybe JSVal -> Maybe HTMLParagraphElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLParagraphElement
HTMLParagraphElement (Maybe JSVal -> Maybe HTMLParagraphElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLParagraphElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLParagraphElement
fromJSValUnchecked = HTMLParagraphElement -> JSM HTMLParagraphElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLParagraphElement -> JSM HTMLParagraphElement)
-> (JSVal -> HTMLParagraphElement)
-> JSVal
-> JSM HTMLParagraphElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLParagraphElement
HTMLParagraphElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLParagraphElement where
  makeObject :: HTMLParagraphElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLParagraphElement -> JSVal)
-> HTMLParagraphElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLParagraphElement -> JSVal
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 :: HTMLParagraphElement -> JSM GType
typeGType HTMLParagraphElement
_ = JSM GType
gTypeHTMLParagraphElement
  {-# INLINE typeGType #-}

noHTMLParagraphElement :: Maybe HTMLParagraphElement
noHTMLParagraphElement :: Maybe HTMLParagraphElement
noHTMLParagraphElement = Maybe HTMLParagraphElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLParagraphElement #-}

gTypeHTMLParagraphElement :: JSM GType
gTypeHTMLParagraphElement :: JSM GType
gTypeHTMLParagraphElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLParagraphElement"

-- | Functions for this inteface are in "JSDOM.HTMLParamElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLParamElement Mozilla HTMLParamElement documentation>
newtype HTMLParamElement = HTMLParamElement { HTMLParamElement -> JSVal
unHTMLParamElement :: JSVal }

instance PToJSVal HTMLParamElement where
  pToJSVal :: HTMLParamElement -> JSVal
pToJSVal = HTMLParamElement -> JSVal
unHTMLParamElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLParamElement where
  pFromJSVal :: JSVal -> HTMLParamElement
pFromJSVal = JSVal -> HTMLParamElement
HTMLParamElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLParamElement where
  toJSVal :: HTMLParamElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLParamElement -> JSVal) -> HTMLParamElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLParamElement -> JSVal
unHTMLParamElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLParamElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLParamElement)
fromJSVal JSVal
v = (JSVal -> HTMLParamElement)
-> Maybe JSVal -> Maybe HTMLParamElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLParamElement
HTMLParamElement (Maybe JSVal -> Maybe HTMLParamElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLParamElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLParamElement
fromJSValUnchecked = HTMLParamElement -> JSM HTMLParamElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLParamElement -> JSM HTMLParamElement)
-> (JSVal -> HTMLParamElement) -> JSVal -> JSM HTMLParamElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLParamElement
HTMLParamElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLParamElement where
  makeObject :: HTMLParamElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLParamElement -> JSVal) -> HTMLParamElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLParamElement -> JSVal
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 :: HTMLParamElement -> JSM GType
typeGType HTMLParamElement
_ = JSM GType
gTypeHTMLParamElement
  {-# INLINE typeGType #-}

noHTMLParamElement :: Maybe HTMLParamElement
noHTMLParamElement :: Maybe HTMLParamElement
noHTMLParamElement = Maybe HTMLParamElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLParamElement #-}

gTypeHTMLParamElement :: JSM GType
gTypeHTMLParamElement :: JSM GType
gTypeHTMLParamElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLParamElement"

-- | Functions for this inteface are in "JSDOM.HTMLPictureElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLPictureElement Mozilla HTMLPictureElement documentation>
newtype HTMLPictureElement = HTMLPictureElement { HTMLPictureElement -> JSVal
unHTMLPictureElement :: JSVal }

instance PToJSVal HTMLPictureElement where
  pToJSVal :: HTMLPictureElement -> JSVal
pToJSVal = HTMLPictureElement -> JSVal
unHTMLPictureElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLPictureElement where
  pFromJSVal :: JSVal -> HTMLPictureElement
pFromJSVal = JSVal -> HTMLPictureElement
HTMLPictureElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLPictureElement where
  toJSVal :: HTMLPictureElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLPictureElement -> JSVal) -> HTMLPictureElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLPictureElement -> JSVal
unHTMLPictureElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLPictureElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLPictureElement)
fromJSVal JSVal
v = (JSVal -> HTMLPictureElement)
-> Maybe JSVal -> Maybe HTMLPictureElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLPictureElement
HTMLPictureElement (Maybe JSVal -> Maybe HTMLPictureElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLPictureElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLPictureElement
fromJSValUnchecked = HTMLPictureElement -> JSM HTMLPictureElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLPictureElement -> JSM HTMLPictureElement)
-> (JSVal -> HTMLPictureElement) -> JSVal -> JSM HTMLPictureElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLPictureElement
HTMLPictureElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLPictureElement where
  makeObject :: HTMLPictureElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLPictureElement -> JSVal)
-> HTMLPictureElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLPictureElement -> JSVal
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 :: HTMLPictureElement -> JSM GType
typeGType HTMLPictureElement
_ = JSM GType
gTypeHTMLPictureElement
  {-# INLINE typeGType #-}

noHTMLPictureElement :: Maybe HTMLPictureElement
noHTMLPictureElement :: Maybe HTMLPictureElement
noHTMLPictureElement = Maybe HTMLPictureElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLPictureElement #-}

gTypeHTMLPictureElement :: JSM GType
gTypeHTMLPictureElement :: JSM GType
gTypeHTMLPictureElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLPictureElement"

-- | Functions for this inteface are in "JSDOM.HTMLPreElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLPreElement Mozilla HTMLPreElement documentation>
newtype HTMLPreElement = HTMLPreElement { HTMLPreElement -> JSVal
unHTMLPreElement :: JSVal }

instance PToJSVal HTMLPreElement where
  pToJSVal :: HTMLPreElement -> JSVal
pToJSVal = HTMLPreElement -> JSVal
unHTMLPreElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLPreElement where
  pFromJSVal :: JSVal -> HTMLPreElement
pFromJSVal = JSVal -> HTMLPreElement
HTMLPreElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLPreElement where
  toJSVal :: HTMLPreElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLPreElement -> JSVal) -> HTMLPreElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLPreElement -> JSVal
unHTMLPreElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLPreElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLPreElement)
fromJSVal JSVal
v = (JSVal -> HTMLPreElement) -> Maybe JSVal -> Maybe HTMLPreElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLPreElement
HTMLPreElement (Maybe JSVal -> Maybe HTMLPreElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLPreElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLPreElement
fromJSValUnchecked = HTMLPreElement -> JSM HTMLPreElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLPreElement -> JSM HTMLPreElement)
-> (JSVal -> HTMLPreElement) -> JSVal -> JSM HTMLPreElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLPreElement
HTMLPreElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLPreElement where
  makeObject :: HTMLPreElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLPreElement -> JSVal) -> HTMLPreElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLPreElement -> JSVal
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 :: HTMLPreElement -> JSM GType
typeGType HTMLPreElement
_ = JSM GType
gTypeHTMLPreElement
  {-# INLINE typeGType #-}

noHTMLPreElement :: Maybe HTMLPreElement
noHTMLPreElement :: Maybe HTMLPreElement
noHTMLPreElement = Maybe HTMLPreElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLPreElement #-}

gTypeHTMLPreElement :: JSM GType
gTypeHTMLPreElement :: JSM GType
gTypeHTMLPreElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLPreElement"

-- | Functions for this inteface are in "JSDOM.HTMLProgressElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLProgressElement Mozilla HTMLProgressElement documentation>
newtype HTMLProgressElement = HTMLProgressElement { HTMLProgressElement -> JSVal
unHTMLProgressElement :: JSVal }

instance PToJSVal HTMLProgressElement where
  pToJSVal :: HTMLProgressElement -> JSVal
pToJSVal = HTMLProgressElement -> JSVal
unHTMLProgressElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLProgressElement where
  pFromJSVal :: JSVal -> HTMLProgressElement
pFromJSVal = JSVal -> HTMLProgressElement
HTMLProgressElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLProgressElement where
  toJSVal :: HTMLProgressElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLProgressElement -> JSVal)
-> HTMLProgressElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLProgressElement -> JSVal
unHTMLProgressElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLProgressElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLProgressElement)
fromJSVal JSVal
v = (JSVal -> HTMLProgressElement)
-> Maybe JSVal -> Maybe HTMLProgressElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLProgressElement
HTMLProgressElement (Maybe JSVal -> Maybe HTMLProgressElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLProgressElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLProgressElement
fromJSValUnchecked = HTMLProgressElement -> JSM HTMLProgressElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLProgressElement -> JSM HTMLProgressElement)
-> (JSVal -> HTMLProgressElement)
-> JSVal
-> JSM HTMLProgressElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLProgressElement
HTMLProgressElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLProgressElement where
  makeObject :: HTMLProgressElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLProgressElement -> JSVal)
-> HTMLProgressElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLProgressElement -> JSVal
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 :: HTMLProgressElement -> JSM GType
typeGType HTMLProgressElement
_ = JSM GType
gTypeHTMLProgressElement
  {-# INLINE typeGType #-}

noHTMLProgressElement :: Maybe HTMLProgressElement
noHTMLProgressElement :: Maybe HTMLProgressElement
noHTMLProgressElement = Maybe HTMLProgressElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLProgressElement #-}

gTypeHTMLProgressElement :: JSM GType
gTypeHTMLProgressElement :: JSM GType
gTypeHTMLProgressElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLProgressElement"

-- | Functions for this inteface are in "JSDOM.HTMLQuoteElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLQuoteElement Mozilla HTMLQuoteElement documentation>
newtype HTMLQuoteElement = HTMLQuoteElement { HTMLQuoteElement -> JSVal
unHTMLQuoteElement :: JSVal }

instance PToJSVal HTMLQuoteElement where
  pToJSVal :: HTMLQuoteElement -> JSVal
pToJSVal = HTMLQuoteElement -> JSVal
unHTMLQuoteElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLQuoteElement where
  pFromJSVal :: JSVal -> HTMLQuoteElement
pFromJSVal = JSVal -> HTMLQuoteElement
HTMLQuoteElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLQuoteElement where
  toJSVal :: HTMLQuoteElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLQuoteElement -> JSVal) -> HTMLQuoteElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLQuoteElement -> JSVal
unHTMLQuoteElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLQuoteElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLQuoteElement)
fromJSVal JSVal
v = (JSVal -> HTMLQuoteElement)
-> Maybe JSVal -> Maybe HTMLQuoteElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLQuoteElement
HTMLQuoteElement (Maybe JSVal -> Maybe HTMLQuoteElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLQuoteElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLQuoteElement
fromJSValUnchecked = HTMLQuoteElement -> JSM HTMLQuoteElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLQuoteElement -> JSM HTMLQuoteElement)
-> (JSVal -> HTMLQuoteElement) -> JSVal -> JSM HTMLQuoteElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLQuoteElement
HTMLQuoteElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLQuoteElement where
  makeObject :: HTMLQuoteElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLQuoteElement -> JSVal) -> HTMLQuoteElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLQuoteElement -> JSVal
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 :: HTMLQuoteElement -> JSM GType
typeGType HTMLQuoteElement
_ = JSM GType
gTypeHTMLQuoteElement
  {-# INLINE typeGType #-}

noHTMLQuoteElement :: Maybe HTMLQuoteElement
noHTMLQuoteElement :: Maybe HTMLQuoteElement
noHTMLQuoteElement = Maybe HTMLQuoteElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLQuoteElement #-}

gTypeHTMLQuoteElement :: JSM GType
gTypeHTMLQuoteElement :: JSM GType
gTypeHTMLQuoteElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLQuoteElement"

-- | Functions for this inteface are in "JSDOM.HTMLScriptElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLScriptElement Mozilla HTMLScriptElement documentation>
newtype HTMLScriptElement = HTMLScriptElement { HTMLScriptElement -> JSVal
unHTMLScriptElement :: JSVal }

instance PToJSVal HTMLScriptElement where
  pToJSVal :: HTMLScriptElement -> JSVal
pToJSVal = HTMLScriptElement -> JSVal
unHTMLScriptElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLScriptElement where
  pFromJSVal :: JSVal -> HTMLScriptElement
pFromJSVal = JSVal -> HTMLScriptElement
HTMLScriptElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLScriptElement where
  toJSVal :: HTMLScriptElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLScriptElement -> JSVal) -> HTMLScriptElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLScriptElement -> JSVal
unHTMLScriptElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLScriptElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLScriptElement)
fromJSVal JSVal
v = (JSVal -> HTMLScriptElement)
-> Maybe JSVal -> Maybe HTMLScriptElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLScriptElement
HTMLScriptElement (Maybe JSVal -> Maybe HTMLScriptElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLScriptElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLScriptElement
fromJSValUnchecked = HTMLScriptElement -> JSM HTMLScriptElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLScriptElement -> JSM HTMLScriptElement)
-> (JSVal -> HTMLScriptElement) -> JSVal -> JSM HTMLScriptElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLScriptElement
HTMLScriptElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLScriptElement where
  makeObject :: HTMLScriptElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLScriptElement -> JSVal) -> HTMLScriptElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLScriptElement -> JSVal
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 :: HTMLScriptElement -> JSM GType
typeGType HTMLScriptElement
_ = JSM GType
gTypeHTMLScriptElement
  {-# INLINE typeGType #-}

noHTMLScriptElement :: Maybe HTMLScriptElement
noHTMLScriptElement :: Maybe HTMLScriptElement
noHTMLScriptElement = Maybe HTMLScriptElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLScriptElement #-}

gTypeHTMLScriptElement :: JSM GType
gTypeHTMLScriptElement :: JSM GType
gTypeHTMLScriptElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLScriptElement"

-- | Functions for this inteface are in "JSDOM.HTMLSelectElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLSelectElement Mozilla HTMLSelectElement documentation>
newtype HTMLSelectElement = HTMLSelectElement { HTMLSelectElement -> JSVal
unHTMLSelectElement :: JSVal }

instance PToJSVal HTMLSelectElement where
  pToJSVal :: HTMLSelectElement -> JSVal
pToJSVal = HTMLSelectElement -> JSVal
unHTMLSelectElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLSelectElement where
  pFromJSVal :: JSVal -> HTMLSelectElement
pFromJSVal = JSVal -> HTMLSelectElement
HTMLSelectElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLSelectElement where
  toJSVal :: HTMLSelectElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLSelectElement -> JSVal) -> HTMLSelectElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLSelectElement -> JSVal
unHTMLSelectElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLSelectElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLSelectElement)
fromJSVal JSVal
v = (JSVal -> HTMLSelectElement)
-> Maybe JSVal -> Maybe HTMLSelectElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLSelectElement
HTMLSelectElement (Maybe JSVal -> Maybe HTMLSelectElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLSelectElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLSelectElement
fromJSValUnchecked = HTMLSelectElement -> JSM HTMLSelectElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLSelectElement -> JSM HTMLSelectElement)
-> (JSVal -> HTMLSelectElement) -> JSVal -> JSM HTMLSelectElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLSelectElement
HTMLSelectElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLSelectElement where
  makeObject :: HTMLSelectElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLSelectElement -> JSVal) -> HTMLSelectElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLSelectElement -> JSVal
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 :: HTMLSelectElement -> JSM GType
typeGType HTMLSelectElement
_ = JSM GType
gTypeHTMLSelectElement
  {-# INLINE typeGType #-}

noHTMLSelectElement :: Maybe HTMLSelectElement
noHTMLSelectElement :: Maybe HTMLSelectElement
noHTMLSelectElement = Maybe HTMLSelectElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLSelectElement #-}

gTypeHTMLSelectElement :: JSM GType
gTypeHTMLSelectElement :: JSM GType
gTypeHTMLSelectElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLSelectElement"

-- | Functions for this inteface are in "JSDOM.HTMLSlotElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLSlotElement Mozilla HTMLSlotElement documentation>
newtype HTMLSlotElement = HTMLSlotElement { HTMLSlotElement -> JSVal
unHTMLSlotElement :: JSVal }

instance PToJSVal HTMLSlotElement where
  pToJSVal :: HTMLSlotElement -> JSVal
pToJSVal = HTMLSlotElement -> JSVal
unHTMLSlotElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLSlotElement where
  pFromJSVal :: JSVal -> HTMLSlotElement
pFromJSVal = JSVal -> HTMLSlotElement
HTMLSlotElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLSlotElement where
  toJSVal :: HTMLSlotElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLSlotElement -> JSVal) -> HTMLSlotElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLSlotElement -> JSVal
unHTMLSlotElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLSlotElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLSlotElement)
fromJSVal JSVal
v = (JSVal -> HTMLSlotElement) -> Maybe JSVal -> Maybe HTMLSlotElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLSlotElement
HTMLSlotElement (Maybe JSVal -> Maybe HTMLSlotElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLSlotElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLSlotElement
fromJSValUnchecked = HTMLSlotElement -> JSM HTMLSlotElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLSlotElement -> JSM HTMLSlotElement)
-> (JSVal -> HTMLSlotElement) -> JSVal -> JSM HTMLSlotElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLSlotElement
HTMLSlotElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLSlotElement where
  makeObject :: HTMLSlotElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLSlotElement -> JSVal) -> HTMLSlotElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLSlotElement -> JSVal
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 :: HTMLSlotElement -> JSM GType
typeGType HTMLSlotElement
_ = JSM GType
gTypeHTMLSlotElement
  {-# INLINE typeGType #-}

noHTMLSlotElement :: Maybe HTMLSlotElement
noHTMLSlotElement :: Maybe HTMLSlotElement
noHTMLSlotElement = Maybe HTMLSlotElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLSlotElement #-}

gTypeHTMLSlotElement :: JSM GType
gTypeHTMLSlotElement :: JSM GType
gTypeHTMLSlotElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLSlotElement"

-- | Functions for this inteface are in "JSDOM.HTMLSourceElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLSourceElement Mozilla HTMLSourceElement documentation>
newtype HTMLSourceElement = HTMLSourceElement { HTMLSourceElement -> JSVal
unHTMLSourceElement :: JSVal }

instance PToJSVal HTMLSourceElement where
  pToJSVal :: HTMLSourceElement -> JSVal
pToJSVal = HTMLSourceElement -> JSVal
unHTMLSourceElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLSourceElement where
  pFromJSVal :: JSVal -> HTMLSourceElement
pFromJSVal = JSVal -> HTMLSourceElement
HTMLSourceElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLSourceElement where
  toJSVal :: HTMLSourceElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLSourceElement -> JSVal) -> HTMLSourceElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLSourceElement -> JSVal
unHTMLSourceElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLSourceElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLSourceElement)
fromJSVal JSVal
v = (JSVal -> HTMLSourceElement)
-> Maybe JSVal -> Maybe HTMLSourceElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLSourceElement
HTMLSourceElement (Maybe JSVal -> Maybe HTMLSourceElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLSourceElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLSourceElement
fromJSValUnchecked = HTMLSourceElement -> JSM HTMLSourceElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLSourceElement -> JSM HTMLSourceElement)
-> (JSVal -> HTMLSourceElement) -> JSVal -> JSM HTMLSourceElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLSourceElement
HTMLSourceElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLSourceElement where
  makeObject :: HTMLSourceElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLSourceElement -> JSVal) -> HTMLSourceElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLSourceElement -> JSVal
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 :: HTMLSourceElement -> JSM GType
typeGType HTMLSourceElement
_ = JSM GType
gTypeHTMLSourceElement
  {-# INLINE typeGType #-}

noHTMLSourceElement :: Maybe HTMLSourceElement
noHTMLSourceElement :: Maybe HTMLSourceElement
noHTMLSourceElement = Maybe HTMLSourceElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLSourceElement #-}

gTypeHTMLSourceElement :: JSM GType
gTypeHTMLSourceElement :: JSM GType
gTypeHTMLSourceElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLSourceElement"

-- | Functions for this inteface are in "JSDOM.HTMLSpanElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLSpanElement Mozilla HTMLSpanElement documentation>
newtype HTMLSpanElement = HTMLSpanElement { HTMLSpanElement -> JSVal
unHTMLSpanElement :: JSVal }

instance PToJSVal HTMLSpanElement where
  pToJSVal :: HTMLSpanElement -> JSVal
pToJSVal = HTMLSpanElement -> JSVal
unHTMLSpanElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLSpanElement where
  pFromJSVal :: JSVal -> HTMLSpanElement
pFromJSVal = JSVal -> HTMLSpanElement
HTMLSpanElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLSpanElement where
  toJSVal :: HTMLSpanElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLSpanElement -> JSVal) -> HTMLSpanElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLSpanElement -> JSVal
unHTMLSpanElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLSpanElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLSpanElement)
fromJSVal JSVal
v = (JSVal -> HTMLSpanElement) -> Maybe JSVal -> Maybe HTMLSpanElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLSpanElement
HTMLSpanElement (Maybe JSVal -> Maybe HTMLSpanElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLSpanElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLSpanElement
fromJSValUnchecked = HTMLSpanElement -> JSM HTMLSpanElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLSpanElement -> JSM HTMLSpanElement)
-> (JSVal -> HTMLSpanElement) -> JSVal -> JSM HTMLSpanElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLSpanElement
HTMLSpanElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLSpanElement where
  makeObject :: HTMLSpanElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLSpanElement -> JSVal) -> HTMLSpanElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLSpanElement -> JSVal
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 :: HTMLSpanElement -> JSM GType
typeGType HTMLSpanElement
_ = JSM GType
gTypeHTMLSpanElement
  {-# INLINE typeGType #-}

noHTMLSpanElement :: Maybe HTMLSpanElement
noHTMLSpanElement :: Maybe HTMLSpanElement
noHTMLSpanElement = Maybe HTMLSpanElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLSpanElement #-}

gTypeHTMLSpanElement :: JSM GType
gTypeHTMLSpanElement :: JSM GType
gTypeHTMLSpanElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLSpanElement"

-- | Functions for this inteface are in "JSDOM.HTMLStyleElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLStyleElement Mozilla HTMLStyleElement documentation>
newtype HTMLStyleElement = HTMLStyleElement { HTMLStyleElement -> JSVal
unHTMLStyleElement :: JSVal }

instance PToJSVal HTMLStyleElement where
  pToJSVal :: HTMLStyleElement -> JSVal
pToJSVal = HTMLStyleElement -> JSVal
unHTMLStyleElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLStyleElement where
  pFromJSVal :: JSVal -> HTMLStyleElement
pFromJSVal = JSVal -> HTMLStyleElement
HTMLStyleElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLStyleElement where
  toJSVal :: HTMLStyleElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLStyleElement -> JSVal) -> HTMLStyleElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLStyleElement -> JSVal
unHTMLStyleElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLStyleElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLStyleElement)
fromJSVal JSVal
v = (JSVal -> HTMLStyleElement)
-> Maybe JSVal -> Maybe HTMLStyleElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLStyleElement
HTMLStyleElement (Maybe JSVal -> Maybe HTMLStyleElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLStyleElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLStyleElement
fromJSValUnchecked = HTMLStyleElement -> JSM HTMLStyleElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLStyleElement -> JSM HTMLStyleElement)
-> (JSVal -> HTMLStyleElement) -> JSVal -> JSM HTMLStyleElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLStyleElement
HTMLStyleElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLStyleElement where
  makeObject :: HTMLStyleElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLStyleElement -> JSVal) -> HTMLStyleElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLStyleElement -> JSVal
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 :: HTMLStyleElement -> JSM GType
typeGType HTMLStyleElement
_ = JSM GType
gTypeHTMLStyleElement
  {-# INLINE typeGType #-}

noHTMLStyleElement :: Maybe HTMLStyleElement
noHTMLStyleElement :: Maybe HTMLStyleElement
noHTMLStyleElement = Maybe HTMLStyleElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLStyleElement #-}

gTypeHTMLStyleElement :: JSM GType
gTypeHTMLStyleElement :: JSM GType
gTypeHTMLStyleElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLStyleElement"

-- | Functions for this inteface are in "JSDOM.HTMLTableCaptionElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLTableCaptionElement Mozilla HTMLTableCaptionElement documentation>
newtype HTMLTableCaptionElement = HTMLTableCaptionElement { HTMLTableCaptionElement -> JSVal
unHTMLTableCaptionElement :: JSVal }

instance PToJSVal HTMLTableCaptionElement where
  pToJSVal :: HTMLTableCaptionElement -> JSVal
pToJSVal = HTMLTableCaptionElement -> JSVal
unHTMLTableCaptionElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLTableCaptionElement where
  pFromJSVal :: JSVal -> HTMLTableCaptionElement
pFromJSVal = JSVal -> HTMLTableCaptionElement
HTMLTableCaptionElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLTableCaptionElement where
  toJSVal :: HTMLTableCaptionElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLTableCaptionElement -> JSVal)
-> HTMLTableCaptionElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableCaptionElement -> JSVal
unHTMLTableCaptionElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLTableCaptionElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLTableCaptionElement)
fromJSVal JSVal
v = (JSVal -> HTMLTableCaptionElement)
-> Maybe JSVal -> Maybe HTMLTableCaptionElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLTableCaptionElement
HTMLTableCaptionElement (Maybe JSVal -> Maybe HTMLTableCaptionElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLTableCaptionElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLTableCaptionElement
fromJSValUnchecked = HTMLTableCaptionElement -> JSM HTMLTableCaptionElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLTableCaptionElement -> JSM HTMLTableCaptionElement)
-> (JSVal -> HTMLTableCaptionElement)
-> JSVal
-> JSM HTMLTableCaptionElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLTableCaptionElement
HTMLTableCaptionElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLTableCaptionElement where
  makeObject :: HTMLTableCaptionElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLTableCaptionElement -> JSVal)
-> HTMLTableCaptionElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableCaptionElement -> JSVal
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 :: HTMLTableCaptionElement -> JSM GType
typeGType HTMLTableCaptionElement
_ = JSM GType
gTypeHTMLTableCaptionElement
  {-# INLINE typeGType #-}

noHTMLTableCaptionElement :: Maybe HTMLTableCaptionElement
noHTMLTableCaptionElement :: Maybe HTMLTableCaptionElement
noHTMLTableCaptionElement = Maybe HTMLTableCaptionElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLTableCaptionElement #-}

gTypeHTMLTableCaptionElement :: JSM GType
gTypeHTMLTableCaptionElement :: JSM GType
gTypeHTMLTableCaptionElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLTableCaptionElement"

-- | Functions for this inteface are in "JSDOM.HTMLTableCellElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLTableCellElement Mozilla HTMLTableCellElement documentation>
newtype HTMLTableCellElement = HTMLTableCellElement { HTMLTableCellElement -> JSVal
unHTMLTableCellElement :: JSVal }

instance PToJSVal HTMLTableCellElement where
  pToJSVal :: HTMLTableCellElement -> JSVal
pToJSVal = HTMLTableCellElement -> JSVal
unHTMLTableCellElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLTableCellElement where
  pFromJSVal :: JSVal -> HTMLTableCellElement
pFromJSVal = JSVal -> HTMLTableCellElement
HTMLTableCellElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLTableCellElement where
  toJSVal :: HTMLTableCellElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLTableCellElement -> JSVal)
-> HTMLTableCellElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableCellElement -> JSVal
unHTMLTableCellElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLTableCellElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLTableCellElement)
fromJSVal JSVal
v = (JSVal -> HTMLTableCellElement)
-> Maybe JSVal -> Maybe HTMLTableCellElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLTableCellElement
HTMLTableCellElement (Maybe JSVal -> Maybe HTMLTableCellElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLTableCellElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLTableCellElement
fromJSValUnchecked = HTMLTableCellElement -> JSM HTMLTableCellElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLTableCellElement -> JSM HTMLTableCellElement)
-> (JSVal -> HTMLTableCellElement)
-> JSVal
-> JSM HTMLTableCellElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLTableCellElement
HTMLTableCellElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLTableCellElement where
  makeObject :: HTMLTableCellElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLTableCellElement -> JSVal)
-> HTMLTableCellElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableCellElement -> JSVal
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 :: HTMLTableCellElement -> JSM GType
typeGType HTMLTableCellElement
_ = JSM GType
gTypeHTMLTableCellElement
  {-# INLINE typeGType #-}

noHTMLTableCellElement :: Maybe HTMLTableCellElement
noHTMLTableCellElement :: Maybe HTMLTableCellElement
noHTMLTableCellElement = Maybe HTMLTableCellElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLTableCellElement #-}

gTypeHTMLTableCellElement :: JSM GType
gTypeHTMLTableCellElement :: JSM GType
gTypeHTMLTableCellElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLTableCellElement"

-- | Functions for this inteface are in "JSDOM.HTMLTableColElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLTableColElement Mozilla HTMLTableColElement documentation>
newtype HTMLTableColElement = HTMLTableColElement { HTMLTableColElement -> JSVal
unHTMLTableColElement :: JSVal }

instance PToJSVal HTMLTableColElement where
  pToJSVal :: HTMLTableColElement -> JSVal
pToJSVal = HTMLTableColElement -> JSVal
unHTMLTableColElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLTableColElement where
  pFromJSVal :: JSVal -> HTMLTableColElement
pFromJSVal = JSVal -> HTMLTableColElement
HTMLTableColElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLTableColElement where
  toJSVal :: HTMLTableColElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLTableColElement -> JSVal)
-> HTMLTableColElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableColElement -> JSVal
unHTMLTableColElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLTableColElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLTableColElement)
fromJSVal JSVal
v = (JSVal -> HTMLTableColElement)
-> Maybe JSVal -> Maybe HTMLTableColElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLTableColElement
HTMLTableColElement (Maybe JSVal -> Maybe HTMLTableColElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLTableColElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLTableColElement
fromJSValUnchecked = HTMLTableColElement -> JSM HTMLTableColElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLTableColElement -> JSM HTMLTableColElement)
-> (JSVal -> HTMLTableColElement)
-> JSVal
-> JSM HTMLTableColElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLTableColElement
HTMLTableColElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLTableColElement where
  makeObject :: HTMLTableColElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLTableColElement -> JSVal)
-> HTMLTableColElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableColElement -> JSVal
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 :: HTMLTableColElement -> JSM GType
typeGType HTMLTableColElement
_ = JSM GType
gTypeHTMLTableColElement
  {-# INLINE typeGType #-}

noHTMLTableColElement :: Maybe HTMLTableColElement
noHTMLTableColElement :: Maybe HTMLTableColElement
noHTMLTableColElement = Maybe HTMLTableColElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLTableColElement #-}

gTypeHTMLTableColElement :: JSM GType
gTypeHTMLTableColElement :: JSM GType
gTypeHTMLTableColElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLTableColElement"

-- | Functions for this inteface are in "JSDOM.HTMLTableElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLTableElement Mozilla HTMLTableElement documentation>
newtype HTMLTableElement = HTMLTableElement { HTMLTableElement -> JSVal
unHTMLTableElement :: JSVal }

instance PToJSVal HTMLTableElement where
  pToJSVal :: HTMLTableElement -> JSVal
pToJSVal = HTMLTableElement -> JSVal
unHTMLTableElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLTableElement where
  pFromJSVal :: JSVal -> HTMLTableElement
pFromJSVal = JSVal -> HTMLTableElement
HTMLTableElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLTableElement where
  toJSVal :: HTMLTableElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLTableElement -> JSVal) -> HTMLTableElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableElement -> JSVal
unHTMLTableElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLTableElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLTableElement)
fromJSVal JSVal
v = (JSVal -> HTMLTableElement)
-> Maybe JSVal -> Maybe HTMLTableElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLTableElement
HTMLTableElement (Maybe JSVal -> Maybe HTMLTableElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLTableElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLTableElement
fromJSValUnchecked = HTMLTableElement -> JSM HTMLTableElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLTableElement -> JSM HTMLTableElement)
-> (JSVal -> HTMLTableElement) -> JSVal -> JSM HTMLTableElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLTableElement
HTMLTableElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLTableElement where
  makeObject :: HTMLTableElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLTableElement -> JSVal) -> HTMLTableElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableElement -> JSVal
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 :: HTMLTableElement -> JSM GType
typeGType HTMLTableElement
_ = JSM GType
gTypeHTMLTableElement
  {-# INLINE typeGType #-}

noHTMLTableElement :: Maybe HTMLTableElement
noHTMLTableElement :: Maybe HTMLTableElement
noHTMLTableElement = Maybe HTMLTableElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLTableElement #-}

gTypeHTMLTableElement :: JSM GType
gTypeHTMLTableElement :: JSM GType
gTypeHTMLTableElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLTableElement"

-- | Functions for this inteface are in "JSDOM.HTMLTableRowElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLTableRowElement Mozilla HTMLTableRowElement documentation>
newtype HTMLTableRowElement = HTMLTableRowElement { HTMLTableRowElement -> JSVal
unHTMLTableRowElement :: JSVal }

instance PToJSVal HTMLTableRowElement where
  pToJSVal :: HTMLTableRowElement -> JSVal
pToJSVal = HTMLTableRowElement -> JSVal
unHTMLTableRowElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLTableRowElement where
  pFromJSVal :: JSVal -> HTMLTableRowElement
pFromJSVal = JSVal -> HTMLTableRowElement
HTMLTableRowElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLTableRowElement where
  toJSVal :: HTMLTableRowElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLTableRowElement -> JSVal)
-> HTMLTableRowElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableRowElement -> JSVal
unHTMLTableRowElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLTableRowElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLTableRowElement)
fromJSVal JSVal
v = (JSVal -> HTMLTableRowElement)
-> Maybe JSVal -> Maybe HTMLTableRowElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLTableRowElement
HTMLTableRowElement (Maybe JSVal -> Maybe HTMLTableRowElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLTableRowElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLTableRowElement
fromJSValUnchecked = HTMLTableRowElement -> JSM HTMLTableRowElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLTableRowElement -> JSM HTMLTableRowElement)
-> (JSVal -> HTMLTableRowElement)
-> JSVal
-> JSM HTMLTableRowElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLTableRowElement
HTMLTableRowElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLTableRowElement where
  makeObject :: HTMLTableRowElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLTableRowElement -> JSVal)
-> HTMLTableRowElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableRowElement -> JSVal
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 :: HTMLTableRowElement -> JSM GType
typeGType HTMLTableRowElement
_ = JSM GType
gTypeHTMLTableRowElement
  {-# INLINE typeGType #-}

noHTMLTableRowElement :: Maybe HTMLTableRowElement
noHTMLTableRowElement :: Maybe HTMLTableRowElement
noHTMLTableRowElement = Maybe HTMLTableRowElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLTableRowElement #-}

gTypeHTMLTableRowElement :: JSM GType
gTypeHTMLTableRowElement :: JSM GType
gTypeHTMLTableRowElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLTableRowElement"

-- | Functions for this inteface are in "JSDOM.HTMLTableSectionElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLTableSectionElement Mozilla HTMLTableSectionElement documentation>
newtype HTMLTableSectionElement = HTMLTableSectionElement { HTMLTableSectionElement -> JSVal
unHTMLTableSectionElement :: JSVal }

instance PToJSVal HTMLTableSectionElement where
  pToJSVal :: HTMLTableSectionElement -> JSVal
pToJSVal = HTMLTableSectionElement -> JSVal
unHTMLTableSectionElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLTableSectionElement where
  pFromJSVal :: JSVal -> HTMLTableSectionElement
pFromJSVal = JSVal -> HTMLTableSectionElement
HTMLTableSectionElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLTableSectionElement where
  toJSVal :: HTMLTableSectionElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLTableSectionElement -> JSVal)
-> HTMLTableSectionElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableSectionElement -> JSVal
unHTMLTableSectionElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLTableSectionElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLTableSectionElement)
fromJSVal JSVal
v = (JSVal -> HTMLTableSectionElement)
-> Maybe JSVal -> Maybe HTMLTableSectionElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLTableSectionElement
HTMLTableSectionElement (Maybe JSVal -> Maybe HTMLTableSectionElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLTableSectionElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLTableSectionElement
fromJSValUnchecked = HTMLTableSectionElement -> JSM HTMLTableSectionElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLTableSectionElement -> JSM HTMLTableSectionElement)
-> (JSVal -> HTMLTableSectionElement)
-> JSVal
-> JSM HTMLTableSectionElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLTableSectionElement
HTMLTableSectionElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLTableSectionElement where
  makeObject :: HTMLTableSectionElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLTableSectionElement -> JSVal)
-> HTMLTableSectionElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTableSectionElement -> JSVal
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 :: HTMLTableSectionElement -> JSM GType
typeGType HTMLTableSectionElement
_ = JSM GType
gTypeHTMLTableSectionElement
  {-# INLINE typeGType #-}

noHTMLTableSectionElement :: Maybe HTMLTableSectionElement
noHTMLTableSectionElement :: Maybe HTMLTableSectionElement
noHTMLTableSectionElement = Maybe HTMLTableSectionElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLTableSectionElement #-}

gTypeHTMLTableSectionElement :: JSM GType
gTypeHTMLTableSectionElement :: JSM GType
gTypeHTMLTableSectionElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLTableSectionElement"

-- | Functions for this inteface are in "JSDOM.HTMLTemplateElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLTemplateElement Mozilla HTMLTemplateElement documentation>
newtype HTMLTemplateElement = HTMLTemplateElement { HTMLTemplateElement -> JSVal
unHTMLTemplateElement :: JSVal }

instance PToJSVal HTMLTemplateElement where
  pToJSVal :: HTMLTemplateElement -> JSVal
pToJSVal = HTMLTemplateElement -> JSVal
unHTMLTemplateElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLTemplateElement where
  pFromJSVal :: JSVal -> HTMLTemplateElement
pFromJSVal = JSVal -> HTMLTemplateElement
HTMLTemplateElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLTemplateElement where
  toJSVal :: HTMLTemplateElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLTemplateElement -> JSVal)
-> HTMLTemplateElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTemplateElement -> JSVal
unHTMLTemplateElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLTemplateElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLTemplateElement)
fromJSVal JSVal
v = (JSVal -> HTMLTemplateElement)
-> Maybe JSVal -> Maybe HTMLTemplateElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLTemplateElement
HTMLTemplateElement (Maybe JSVal -> Maybe HTMLTemplateElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLTemplateElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLTemplateElement
fromJSValUnchecked = HTMLTemplateElement -> JSM HTMLTemplateElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLTemplateElement -> JSM HTMLTemplateElement)
-> (JSVal -> HTMLTemplateElement)
-> JSVal
-> JSM HTMLTemplateElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLTemplateElement
HTMLTemplateElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLTemplateElement where
  makeObject :: HTMLTemplateElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLTemplateElement -> JSVal)
-> HTMLTemplateElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTemplateElement -> JSVal
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 :: HTMLTemplateElement -> JSM GType
typeGType HTMLTemplateElement
_ = JSM GType
gTypeHTMLTemplateElement
  {-# INLINE typeGType #-}

noHTMLTemplateElement :: Maybe HTMLTemplateElement
noHTMLTemplateElement :: Maybe HTMLTemplateElement
noHTMLTemplateElement = Maybe HTMLTemplateElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLTemplateElement #-}

gTypeHTMLTemplateElement :: JSM GType
gTypeHTMLTemplateElement :: JSM GType
gTypeHTMLTemplateElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLTemplateElement"

-- | Functions for this inteface are in "JSDOM.HTMLTextAreaElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLTextAreaElement Mozilla HTMLTextAreaElement documentation>
newtype HTMLTextAreaElement = HTMLTextAreaElement { HTMLTextAreaElement -> JSVal
unHTMLTextAreaElement :: JSVal }

instance PToJSVal HTMLTextAreaElement where
  pToJSVal :: HTMLTextAreaElement -> JSVal
pToJSVal = HTMLTextAreaElement -> JSVal
unHTMLTextAreaElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLTextAreaElement where
  pFromJSVal :: JSVal -> HTMLTextAreaElement
pFromJSVal = JSVal -> HTMLTextAreaElement
HTMLTextAreaElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLTextAreaElement where
  toJSVal :: HTMLTextAreaElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLTextAreaElement -> JSVal)
-> HTMLTextAreaElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTextAreaElement -> JSVal
unHTMLTextAreaElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLTextAreaElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLTextAreaElement)
fromJSVal JSVal
v = (JSVal -> HTMLTextAreaElement)
-> Maybe JSVal -> Maybe HTMLTextAreaElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLTextAreaElement
HTMLTextAreaElement (Maybe JSVal -> Maybe HTMLTextAreaElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLTextAreaElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLTextAreaElement
fromJSValUnchecked = HTMLTextAreaElement -> JSM HTMLTextAreaElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLTextAreaElement -> JSM HTMLTextAreaElement)
-> (JSVal -> HTMLTextAreaElement)
-> JSVal
-> JSM HTMLTextAreaElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLTextAreaElement
HTMLTextAreaElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLTextAreaElement where
  makeObject :: HTMLTextAreaElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLTextAreaElement -> JSVal)
-> HTMLTextAreaElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTextAreaElement -> JSVal
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 :: HTMLTextAreaElement -> JSM GType
typeGType HTMLTextAreaElement
_ = JSM GType
gTypeHTMLTextAreaElement
  {-# INLINE typeGType #-}

noHTMLTextAreaElement :: Maybe HTMLTextAreaElement
noHTMLTextAreaElement :: Maybe HTMLTextAreaElement
noHTMLTextAreaElement = Maybe HTMLTextAreaElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLTextAreaElement #-}

gTypeHTMLTextAreaElement :: JSM GType
gTypeHTMLTextAreaElement :: JSM GType
gTypeHTMLTextAreaElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLTextAreaElement"

-- | Functions for this inteface are in "JSDOM.HTMLTimeElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLTimeElement Mozilla HTMLTimeElement documentation>
newtype HTMLTimeElement = HTMLTimeElement { HTMLTimeElement -> JSVal
unHTMLTimeElement :: JSVal }

instance PToJSVal HTMLTimeElement where
  pToJSVal :: HTMLTimeElement -> JSVal
pToJSVal = HTMLTimeElement -> JSVal
unHTMLTimeElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLTimeElement where
  pFromJSVal :: JSVal -> HTMLTimeElement
pFromJSVal = JSVal -> HTMLTimeElement
HTMLTimeElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLTimeElement where
  toJSVal :: HTMLTimeElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLTimeElement -> JSVal) -> HTMLTimeElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTimeElement -> JSVal
unHTMLTimeElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLTimeElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLTimeElement)
fromJSVal JSVal
v = (JSVal -> HTMLTimeElement) -> Maybe JSVal -> Maybe HTMLTimeElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLTimeElement
HTMLTimeElement (Maybe JSVal -> Maybe HTMLTimeElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLTimeElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLTimeElement
fromJSValUnchecked = HTMLTimeElement -> JSM HTMLTimeElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLTimeElement -> JSM HTMLTimeElement)
-> (JSVal -> HTMLTimeElement) -> JSVal -> JSM HTMLTimeElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLTimeElement
HTMLTimeElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLTimeElement where
  makeObject :: HTMLTimeElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLTimeElement -> JSVal) -> HTMLTimeElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTimeElement -> JSVal
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 :: HTMLTimeElement -> JSM GType
typeGType HTMLTimeElement
_ = JSM GType
gTypeHTMLTimeElement
  {-# INLINE typeGType #-}

noHTMLTimeElement :: Maybe HTMLTimeElement
noHTMLTimeElement :: Maybe HTMLTimeElement
noHTMLTimeElement = Maybe HTMLTimeElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLTimeElement #-}

gTypeHTMLTimeElement :: JSM GType
gTypeHTMLTimeElement :: JSM GType
gTypeHTMLTimeElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLTimeElement"

-- | Functions for this inteface are in "JSDOM.HTMLTitleElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLTitleElement Mozilla HTMLTitleElement documentation>
newtype HTMLTitleElement = HTMLTitleElement { HTMLTitleElement -> JSVal
unHTMLTitleElement :: JSVal }

instance PToJSVal HTMLTitleElement where
  pToJSVal :: HTMLTitleElement -> JSVal
pToJSVal = HTMLTitleElement -> JSVal
unHTMLTitleElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLTitleElement where
  pFromJSVal :: JSVal -> HTMLTitleElement
pFromJSVal = JSVal -> HTMLTitleElement
HTMLTitleElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLTitleElement where
  toJSVal :: HTMLTitleElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLTitleElement -> JSVal) -> HTMLTitleElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTitleElement -> JSVal
unHTMLTitleElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLTitleElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLTitleElement)
fromJSVal JSVal
v = (JSVal -> HTMLTitleElement)
-> Maybe JSVal -> Maybe HTMLTitleElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLTitleElement
HTMLTitleElement (Maybe JSVal -> Maybe HTMLTitleElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLTitleElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLTitleElement
fromJSValUnchecked = HTMLTitleElement -> JSM HTMLTitleElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLTitleElement -> JSM HTMLTitleElement)
-> (JSVal -> HTMLTitleElement) -> JSVal -> JSM HTMLTitleElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLTitleElement
HTMLTitleElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLTitleElement where
  makeObject :: HTMLTitleElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLTitleElement -> JSVal) -> HTMLTitleElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTitleElement -> JSVal
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 :: HTMLTitleElement -> JSM GType
typeGType HTMLTitleElement
_ = JSM GType
gTypeHTMLTitleElement
  {-# INLINE typeGType #-}

noHTMLTitleElement :: Maybe HTMLTitleElement
noHTMLTitleElement :: Maybe HTMLTitleElement
noHTMLTitleElement = Maybe HTMLTitleElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLTitleElement #-}

gTypeHTMLTitleElement :: JSM GType
gTypeHTMLTitleElement :: JSM GType
gTypeHTMLTitleElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLTitleElement"

-- | Functions for this inteface are in "JSDOM.HTMLTrackElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLTrackElement Mozilla HTMLTrackElement documentation>
newtype HTMLTrackElement = HTMLTrackElement { HTMLTrackElement -> JSVal
unHTMLTrackElement :: JSVal }

instance PToJSVal HTMLTrackElement where
  pToJSVal :: HTMLTrackElement -> JSVal
pToJSVal = HTMLTrackElement -> JSVal
unHTMLTrackElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLTrackElement where
  pFromJSVal :: JSVal -> HTMLTrackElement
pFromJSVal = JSVal -> HTMLTrackElement
HTMLTrackElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLTrackElement where
  toJSVal :: HTMLTrackElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLTrackElement -> JSVal) -> HTMLTrackElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTrackElement -> JSVal
unHTMLTrackElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLTrackElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLTrackElement)
fromJSVal JSVal
v = (JSVal -> HTMLTrackElement)
-> Maybe JSVal -> Maybe HTMLTrackElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLTrackElement
HTMLTrackElement (Maybe JSVal -> Maybe HTMLTrackElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLTrackElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLTrackElement
fromJSValUnchecked = HTMLTrackElement -> JSM HTMLTrackElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLTrackElement -> JSM HTMLTrackElement)
-> (JSVal -> HTMLTrackElement) -> JSVal -> JSM HTMLTrackElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLTrackElement
HTMLTrackElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLTrackElement where
  makeObject :: HTMLTrackElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLTrackElement -> JSVal) -> HTMLTrackElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLTrackElement -> JSVal
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 :: HTMLTrackElement -> JSM GType
typeGType HTMLTrackElement
_ = JSM GType
gTypeHTMLTrackElement
  {-# INLINE typeGType #-}

noHTMLTrackElement :: Maybe HTMLTrackElement
noHTMLTrackElement :: Maybe HTMLTrackElement
noHTMLTrackElement = Maybe HTMLTrackElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLTrackElement #-}

gTypeHTMLTrackElement :: JSM GType
gTypeHTMLTrackElement :: JSM GType
gTypeHTMLTrackElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLTrackElement"

-- | Functions for this inteface are in "JSDOM.HTMLUListElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLUListElement Mozilla HTMLUListElement documentation>
newtype HTMLUListElement = HTMLUListElement { HTMLUListElement -> JSVal
unHTMLUListElement :: JSVal }

instance PToJSVal HTMLUListElement where
  pToJSVal :: HTMLUListElement -> JSVal
pToJSVal = HTMLUListElement -> JSVal
unHTMLUListElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLUListElement where
  pFromJSVal :: JSVal -> HTMLUListElement
pFromJSVal = JSVal -> HTMLUListElement
HTMLUListElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLUListElement where
  toJSVal :: HTMLUListElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLUListElement -> JSVal) -> HTMLUListElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLUListElement -> JSVal
unHTMLUListElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLUListElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLUListElement)
fromJSVal JSVal
v = (JSVal -> HTMLUListElement)
-> Maybe JSVal -> Maybe HTMLUListElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLUListElement
HTMLUListElement (Maybe JSVal -> Maybe HTMLUListElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLUListElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLUListElement
fromJSValUnchecked = HTMLUListElement -> JSM HTMLUListElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLUListElement -> JSM HTMLUListElement)
-> (JSVal -> HTMLUListElement) -> JSVal -> JSM HTMLUListElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLUListElement
HTMLUListElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLUListElement where
  makeObject :: HTMLUListElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLUListElement -> JSVal) -> HTMLUListElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLUListElement -> JSVal
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 :: HTMLUListElement -> JSM GType
typeGType HTMLUListElement
_ = JSM GType
gTypeHTMLUListElement
  {-# INLINE typeGType #-}

noHTMLUListElement :: Maybe HTMLUListElement
noHTMLUListElement :: Maybe HTMLUListElement
noHTMLUListElement = Maybe HTMLUListElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLUListElement #-}

gTypeHTMLUListElement :: JSM GType
gTypeHTMLUListElement :: JSM GType
gTypeHTMLUListElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLUListElement"

-- | Functions for this inteface are in "JSDOM.HTMLUnknownElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLUnknownElement Mozilla HTMLUnknownElement documentation>
newtype HTMLUnknownElement = HTMLUnknownElement { HTMLUnknownElement -> JSVal
unHTMLUnknownElement :: JSVal }

instance PToJSVal HTMLUnknownElement where
  pToJSVal :: HTMLUnknownElement -> JSVal
pToJSVal = HTMLUnknownElement -> JSVal
unHTMLUnknownElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLUnknownElement where
  pFromJSVal :: JSVal -> HTMLUnknownElement
pFromJSVal = JSVal -> HTMLUnknownElement
HTMLUnknownElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLUnknownElement where
  toJSVal :: HTMLUnknownElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLUnknownElement -> JSVal) -> HTMLUnknownElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLUnknownElement -> JSVal
unHTMLUnknownElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLUnknownElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLUnknownElement)
fromJSVal JSVal
v = (JSVal -> HTMLUnknownElement)
-> Maybe JSVal -> Maybe HTMLUnknownElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLUnknownElement
HTMLUnknownElement (Maybe JSVal -> Maybe HTMLUnknownElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLUnknownElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLUnknownElement
fromJSValUnchecked = HTMLUnknownElement -> JSM HTMLUnknownElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLUnknownElement -> JSM HTMLUnknownElement)
-> (JSVal -> HTMLUnknownElement) -> JSVal -> JSM HTMLUnknownElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLUnknownElement
HTMLUnknownElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLUnknownElement where
  makeObject :: HTMLUnknownElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLUnknownElement -> JSVal)
-> HTMLUnknownElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLUnknownElement -> JSVal
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 :: HTMLUnknownElement -> JSM GType
typeGType HTMLUnknownElement
_ = JSM GType
gTypeHTMLUnknownElement
  {-# INLINE typeGType #-}

noHTMLUnknownElement :: Maybe HTMLUnknownElement
noHTMLUnknownElement :: Maybe HTMLUnknownElement
noHTMLUnknownElement = Maybe HTMLUnknownElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLUnknownElement #-}

gTypeHTMLUnknownElement :: JSM GType
gTypeHTMLUnknownElement :: JSM GType
gTypeHTMLUnknownElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLUnknownElement"

-- | Functions for this inteface are in "JSDOM.HTMLVideoElement".
-- Base interface functions are in:
--
--     * "JSDOM.HTMLMediaElement"
--     * "JSDOM.HTMLElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HTMLVideoElement Mozilla HTMLVideoElement documentation>
newtype HTMLVideoElement = HTMLVideoElement { HTMLVideoElement -> JSVal
unHTMLVideoElement :: JSVal }

instance PToJSVal HTMLVideoElement where
  pToJSVal :: HTMLVideoElement -> JSVal
pToJSVal = HTMLVideoElement -> JSVal
unHTMLVideoElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal HTMLVideoElement where
  pFromJSVal :: JSVal -> HTMLVideoElement
pFromJSVal = JSVal -> HTMLVideoElement
HTMLVideoElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal HTMLVideoElement where
  toJSVal :: HTMLVideoElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HTMLVideoElement -> JSVal) -> HTMLVideoElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLVideoElement -> JSVal
unHTMLVideoElement
  {-# INLINE toJSVal #-}

instance FromJSVal HTMLVideoElement where
  fromJSVal :: JSVal -> JSM (Maybe HTMLVideoElement)
fromJSVal JSVal
v = (JSVal -> HTMLVideoElement)
-> Maybe JSVal -> Maybe HTMLVideoElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HTMLVideoElement
HTMLVideoElement (Maybe JSVal -> Maybe HTMLVideoElement)
-> JSM (Maybe JSVal) -> JSM (Maybe HTMLVideoElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HTMLVideoElement
fromJSValUnchecked = HTMLVideoElement -> JSM HTMLVideoElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HTMLVideoElement -> JSM HTMLVideoElement)
-> (JSVal -> HTMLVideoElement) -> JSVal -> JSM HTMLVideoElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HTMLVideoElement
HTMLVideoElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HTMLVideoElement where
  makeObject :: HTMLVideoElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HTMLVideoElement -> JSVal) -> HTMLVideoElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLVideoElement -> JSVal
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 :: HTMLVideoElement -> JSM GType
typeGType HTMLVideoElement
_ = JSM GType
gTypeHTMLVideoElement
  {-# INLINE typeGType #-}

noHTMLVideoElement :: Maybe HTMLVideoElement
noHTMLVideoElement :: Maybe HTMLVideoElement
noHTMLVideoElement = Maybe HTMLVideoElement
forall a. Maybe a
Nothing
{-# INLINE noHTMLVideoElement #-}

gTypeHTMLVideoElement :: JSM GType
gTypeHTMLVideoElement :: JSM GType
gTypeHTMLVideoElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HTMLVideoElement"

-- | Functions for this inteface are in "JSDOM.HashChangeEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HashChangeEvent Mozilla HashChangeEvent documentation>
newtype HashChangeEvent = HashChangeEvent { HashChangeEvent -> JSVal
unHashChangeEvent :: JSVal }

instance PToJSVal HashChangeEvent where
  pToJSVal :: HashChangeEvent -> JSVal
pToJSVal = HashChangeEvent -> JSVal
unHashChangeEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal HashChangeEvent where
  pFromJSVal :: JSVal -> HashChangeEvent
pFromJSVal = JSVal -> HashChangeEvent
HashChangeEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal HashChangeEvent where
  toJSVal :: HashChangeEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HashChangeEvent -> JSVal) -> HashChangeEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashChangeEvent -> JSVal
unHashChangeEvent
  {-# INLINE toJSVal #-}

instance FromJSVal HashChangeEvent where
  fromJSVal :: JSVal -> JSM (Maybe HashChangeEvent)
fromJSVal JSVal
v = (JSVal -> HashChangeEvent) -> Maybe JSVal -> Maybe HashChangeEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HashChangeEvent
HashChangeEvent (Maybe JSVal -> Maybe HashChangeEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe HashChangeEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HashChangeEvent
fromJSValUnchecked = HashChangeEvent -> JSM HashChangeEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HashChangeEvent -> JSM HashChangeEvent)
-> (JSVal -> HashChangeEvent) -> JSVal -> JSM HashChangeEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HashChangeEvent
HashChangeEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HashChangeEvent where
  makeObject :: HashChangeEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HashChangeEvent -> JSVal) -> HashChangeEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashChangeEvent -> JSVal
unHashChangeEvent

instance IsEvent HashChangeEvent
instance IsGObject HashChangeEvent where
  typeGType :: HashChangeEvent -> JSM GType
typeGType HashChangeEvent
_ = JSM GType
gTypeHashChangeEvent
  {-# INLINE typeGType #-}

noHashChangeEvent :: Maybe HashChangeEvent
noHashChangeEvent :: Maybe HashChangeEvent
noHashChangeEvent = Maybe HashChangeEvent
forall a. Maybe a
Nothing
{-# INLINE noHashChangeEvent #-}

gTypeHashChangeEvent :: JSM GType
gTypeHashChangeEvent :: JSM GType
gTypeHashChangeEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HashChangeEvent"

-- | Functions for this inteface are in "JSDOM.HashChangeEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HashChangeEventInit Mozilla HashChangeEventInit documentation>
newtype HashChangeEventInit = HashChangeEventInit { HashChangeEventInit -> JSVal
unHashChangeEventInit :: JSVal }

instance PToJSVal HashChangeEventInit where
  pToJSVal :: HashChangeEventInit -> JSVal
pToJSVal = HashChangeEventInit -> JSVal
unHashChangeEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal HashChangeEventInit where
  pFromJSVal :: JSVal -> HashChangeEventInit
pFromJSVal = JSVal -> HashChangeEventInit
HashChangeEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal HashChangeEventInit where
  toJSVal :: HashChangeEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HashChangeEventInit -> JSVal)
-> HashChangeEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashChangeEventInit -> JSVal
unHashChangeEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal HashChangeEventInit where
  fromJSVal :: JSVal -> JSM (Maybe HashChangeEventInit)
fromJSVal JSVal
v = (JSVal -> HashChangeEventInit)
-> Maybe JSVal -> Maybe HashChangeEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HashChangeEventInit
HashChangeEventInit (Maybe JSVal -> Maybe HashChangeEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe HashChangeEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HashChangeEventInit
fromJSValUnchecked = HashChangeEventInit -> JSM HashChangeEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HashChangeEventInit -> JSM HashChangeEventInit)
-> (JSVal -> HashChangeEventInit)
-> JSVal
-> JSM HashChangeEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HashChangeEventInit
HashChangeEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HashChangeEventInit where
  makeObject :: HashChangeEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HashChangeEventInit -> JSVal)
-> HashChangeEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashChangeEventInit -> JSVal
unHashChangeEventInit

instance IsEventInit HashChangeEventInit
instance IsGObject HashChangeEventInit where
  typeGType :: HashChangeEventInit -> JSM GType
typeGType HashChangeEventInit
_ = JSM GType
gTypeHashChangeEventInit
  {-# INLINE typeGType #-}

noHashChangeEventInit :: Maybe HashChangeEventInit
noHashChangeEventInit :: Maybe HashChangeEventInit
noHashChangeEventInit = Maybe HashChangeEventInit
forall a. Maybe a
Nothing
{-# INLINE noHashChangeEventInit #-}

gTypeHashChangeEventInit :: JSM GType
gTypeHashChangeEventInit :: JSM GType
gTypeHashChangeEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HashChangeEventInit"

-- | Functions for this inteface are in "JSDOM.Headers".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Headers Mozilla Headers documentation>
newtype Headers = Headers { Headers -> JSVal
unHeaders :: JSVal }

instance PToJSVal Headers where
  pToJSVal :: Headers -> JSVal
pToJSVal = Headers -> JSVal
unHeaders
  {-# INLINE pToJSVal #-}

instance PFromJSVal Headers where
  pFromJSVal :: JSVal -> Headers
pFromJSVal = JSVal -> Headers
Headers
  {-# INLINE pFromJSVal #-}

instance ToJSVal Headers where
  toJSVal :: Headers -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Headers -> JSVal) -> Headers -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Headers -> JSVal
unHeaders
  {-# INLINE toJSVal #-}

instance FromJSVal Headers where
  fromJSVal :: JSVal -> JSM (Maybe Headers)
fromJSVal JSVal
v = (JSVal -> Headers) -> Maybe JSVal -> Maybe Headers
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Headers
Headers (Maybe JSVal -> Maybe Headers)
-> JSM (Maybe JSVal) -> JSM (Maybe Headers)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Headers
fromJSValUnchecked = Headers -> JSM Headers
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Headers -> JSM Headers)
-> (JSVal -> Headers) -> JSVal -> JSM Headers
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Headers
Headers
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Headers where
  makeObject :: Headers -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Headers -> JSVal) -> Headers -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Headers -> JSVal
unHeaders

instance IsGObject Headers where
  typeGType :: Headers -> JSM GType
typeGType Headers
_ = JSM GType
gTypeHeaders
  {-# INLINE typeGType #-}

noHeaders :: Maybe Headers
noHeaders :: Maybe Headers
noHeaders = Maybe Headers
forall a. Maybe a
Nothing
{-# INLINE noHeaders #-}

gTypeHeaders :: JSM GType
gTypeHeaders :: JSM GType
gTypeHeaders = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Headers"

-- | Functions for this inteface are in "JSDOM.History".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/History Mozilla History documentation>
newtype History = History { History -> JSVal
unHistory :: JSVal }

instance PToJSVal History where
  pToJSVal :: History -> JSVal
pToJSVal = History -> JSVal
unHistory
  {-# INLINE pToJSVal #-}

instance PFromJSVal History where
  pFromJSVal :: JSVal -> History
pFromJSVal = JSVal -> History
History
  {-# INLINE pFromJSVal #-}

instance ToJSVal History where
  toJSVal :: History -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (History -> JSVal) -> History -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. History -> JSVal
unHistory
  {-# INLINE toJSVal #-}

instance FromJSVal History where
  fromJSVal :: JSVal -> JSM (Maybe History)
fromJSVal JSVal
v = (JSVal -> History) -> Maybe JSVal -> Maybe History
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> History
History (Maybe JSVal -> Maybe History)
-> JSM (Maybe JSVal) -> JSM (Maybe History)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM History
fromJSValUnchecked = History -> JSM History
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (History -> JSM History)
-> (JSVal -> History) -> JSVal -> JSM History
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> History
History
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject History where
  makeObject :: History -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (History -> JSVal) -> History -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. History -> JSVal
unHistory

instance IsGObject History where
  typeGType :: History -> JSM GType
typeGType History
_ = JSM GType
gTypeHistory
  {-# INLINE typeGType #-}

noHistory :: Maybe History
noHistory :: Maybe History
noHistory = Maybe History
forall a. Maybe a
Nothing
{-# INLINE noHistory #-}

gTypeHistory :: JSM GType
gTypeHistory :: JSM GType
gTypeHistory = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"History"

-- | Functions for this inteface are in "JSDOM.HkdfParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HkdfParams Mozilla HkdfParams documentation>
newtype HkdfParams = HkdfParams { HkdfParams -> JSVal
unHkdfParams :: JSVal }

instance PToJSVal HkdfParams where
  pToJSVal :: HkdfParams -> JSVal
pToJSVal = HkdfParams -> JSVal
unHkdfParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal HkdfParams where
  pFromJSVal :: JSVal -> HkdfParams
pFromJSVal = JSVal -> HkdfParams
HkdfParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal HkdfParams where
  toJSVal :: HkdfParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HkdfParams -> JSVal) -> HkdfParams -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HkdfParams -> JSVal
unHkdfParams
  {-# INLINE toJSVal #-}

instance FromJSVal HkdfParams where
  fromJSVal :: JSVal -> JSM (Maybe HkdfParams)
fromJSVal JSVal
v = (JSVal -> HkdfParams) -> Maybe JSVal -> Maybe HkdfParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HkdfParams
HkdfParams (Maybe JSVal -> Maybe HkdfParams)
-> JSM (Maybe JSVal) -> JSM (Maybe HkdfParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HkdfParams
fromJSValUnchecked = HkdfParams -> JSM HkdfParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HkdfParams -> JSM HkdfParams)
-> (JSVal -> HkdfParams) -> JSVal -> JSM HkdfParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HkdfParams
HkdfParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HkdfParams where
  makeObject :: HkdfParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HkdfParams -> JSVal) -> HkdfParams -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HkdfParams -> JSVal
unHkdfParams

instance IsCryptoAlgorithmParameters HkdfParams
instance IsGObject HkdfParams where
  typeGType :: HkdfParams -> JSM GType
typeGType HkdfParams
_ = JSM GType
gTypeHkdfParams
  {-# INLINE typeGType #-}

noHkdfParams :: Maybe HkdfParams
noHkdfParams :: Maybe HkdfParams
noHkdfParams = Maybe HkdfParams
forall a. Maybe a
Nothing
{-# INLINE noHkdfParams #-}

gTypeHkdfParams :: JSM GType
gTypeHkdfParams :: JSM GType
gTypeHkdfParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HkdfParams"

-- | Functions for this inteface are in "JSDOM.HmacKeyParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/HmacKeyParams Mozilla HmacKeyParams documentation>
newtype HmacKeyParams = HmacKeyParams { HmacKeyParams -> JSVal
unHmacKeyParams :: JSVal }

instance PToJSVal HmacKeyParams where
  pToJSVal :: HmacKeyParams -> JSVal
pToJSVal = HmacKeyParams -> JSVal
unHmacKeyParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal HmacKeyParams where
  pFromJSVal :: JSVal -> HmacKeyParams
pFromJSVal = JSVal -> HmacKeyParams
HmacKeyParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal HmacKeyParams where
  toJSVal :: HmacKeyParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (HmacKeyParams -> JSVal) -> HmacKeyParams -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HmacKeyParams -> JSVal
unHmacKeyParams
  {-# INLINE toJSVal #-}

instance FromJSVal HmacKeyParams where
  fromJSVal :: JSVal -> JSM (Maybe HmacKeyParams)
fromJSVal JSVal
v = (JSVal -> HmacKeyParams) -> Maybe JSVal -> Maybe HmacKeyParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> HmacKeyParams
HmacKeyParams (Maybe JSVal -> Maybe HmacKeyParams)
-> JSM (Maybe JSVal) -> JSM (Maybe HmacKeyParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM HmacKeyParams
fromJSValUnchecked = HmacKeyParams -> JSM HmacKeyParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (HmacKeyParams -> JSM HmacKeyParams)
-> (JSVal -> HmacKeyParams) -> JSVal -> JSM HmacKeyParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> HmacKeyParams
HmacKeyParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject HmacKeyParams where
  makeObject :: HmacKeyParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (HmacKeyParams -> JSVal) -> HmacKeyParams -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HmacKeyParams -> JSVal
unHmacKeyParams

instance IsCryptoAlgorithmParameters HmacKeyParams
instance IsGObject HmacKeyParams where
  typeGType :: HmacKeyParams -> JSM GType
typeGType HmacKeyParams
_ = JSM GType
gTypeHmacKeyParams
  {-# INLINE typeGType #-}

noHmacKeyParams :: Maybe HmacKeyParams
noHmacKeyParams :: Maybe HmacKeyParams
noHmacKeyParams = Maybe HmacKeyParams
forall a. Maybe a
Nothing
{-# INLINE noHmacKeyParams #-}

gTypeHmacKeyParams :: JSM GType
gTypeHmacKeyParams :: JSM GType
gTypeHmacKeyParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"HmacKeyParams"

-- | Functions for this inteface are in "JSDOM.IDBCursor".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBCursor Mozilla IDBCursor documentation>
newtype IDBCursor = IDBCursor { IDBCursor -> JSVal
unIDBCursor :: JSVal }

instance PToJSVal IDBCursor where
  pToJSVal :: IDBCursor -> JSVal
pToJSVal = IDBCursor -> JSVal
unIDBCursor
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBCursor where
  pFromJSVal :: JSVal -> IDBCursor
pFromJSVal = JSVal -> IDBCursor
IDBCursor
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBCursor where
  toJSVal :: IDBCursor -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBCursor -> JSVal) -> IDBCursor -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBCursor -> JSVal
unIDBCursor
  {-# INLINE toJSVal #-}

instance FromJSVal IDBCursor where
  fromJSVal :: JSVal -> JSM (Maybe IDBCursor)
fromJSVal JSVal
v = (JSVal -> IDBCursor) -> Maybe JSVal -> Maybe IDBCursor
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBCursor
IDBCursor (Maybe JSVal -> Maybe IDBCursor)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBCursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBCursor
fromJSValUnchecked = IDBCursor -> JSM IDBCursor
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBCursor -> JSM IDBCursor)
-> (JSVal -> IDBCursor) -> JSVal -> JSM IDBCursor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBCursor
IDBCursor
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBCursor where
  makeObject :: IDBCursor -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBCursor -> JSVal) -> IDBCursor -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBCursor -> JSVal
unIDBCursor

class (IsGObject o) => IsIDBCursor o
toIDBCursor :: IsIDBCursor o => o -> IDBCursor
toIDBCursor :: forall o. IsIDBCursor o => o -> IDBCursor
toIDBCursor = JSVal -> IDBCursor
IDBCursor (JSVal -> IDBCursor) -> (o -> JSVal) -> o -> IDBCursor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsIDBCursor IDBCursor
instance IsGObject IDBCursor where
  typeGType :: IDBCursor -> JSM GType
typeGType IDBCursor
_ = JSM GType
gTypeIDBCursor
  {-# INLINE typeGType #-}

noIDBCursor :: Maybe IDBCursor
noIDBCursor :: Maybe IDBCursor
noIDBCursor = Maybe IDBCursor
forall a. Maybe a
Nothing
{-# INLINE noIDBCursor #-}

gTypeIDBCursor :: JSM GType
gTypeIDBCursor :: JSM GType
gTypeIDBCursor = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBCursor"

-- | Functions for this inteface are in "JSDOM.IDBCursorWithValue".
-- Base interface functions are in:
--
--     * "JSDOM.IDBCursor"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBCursorWithValue Mozilla IDBCursorWithValue documentation>
newtype IDBCursorWithValue = IDBCursorWithValue { IDBCursorWithValue -> JSVal
unIDBCursorWithValue :: JSVal }

instance PToJSVal IDBCursorWithValue where
  pToJSVal :: IDBCursorWithValue -> JSVal
pToJSVal = IDBCursorWithValue -> JSVal
unIDBCursorWithValue
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBCursorWithValue where
  pFromJSVal :: JSVal -> IDBCursorWithValue
pFromJSVal = JSVal -> IDBCursorWithValue
IDBCursorWithValue
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBCursorWithValue where
  toJSVal :: IDBCursorWithValue -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBCursorWithValue -> JSVal) -> IDBCursorWithValue -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBCursorWithValue -> JSVal
unIDBCursorWithValue
  {-# INLINE toJSVal #-}

instance FromJSVal IDBCursorWithValue where
  fromJSVal :: JSVal -> JSM (Maybe IDBCursorWithValue)
fromJSVal JSVal
v = (JSVal -> IDBCursorWithValue)
-> Maybe JSVal -> Maybe IDBCursorWithValue
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBCursorWithValue
IDBCursorWithValue (Maybe JSVal -> Maybe IDBCursorWithValue)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBCursorWithValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBCursorWithValue
fromJSValUnchecked = IDBCursorWithValue -> JSM IDBCursorWithValue
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBCursorWithValue -> JSM IDBCursorWithValue)
-> (JSVal -> IDBCursorWithValue) -> JSVal -> JSM IDBCursorWithValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBCursorWithValue
IDBCursorWithValue
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBCursorWithValue where
  makeObject :: IDBCursorWithValue -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBCursorWithValue -> JSVal)
-> IDBCursorWithValue
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBCursorWithValue -> JSVal
unIDBCursorWithValue

instance IsIDBCursor IDBCursorWithValue
instance IsGObject IDBCursorWithValue where
  typeGType :: IDBCursorWithValue -> JSM GType
typeGType IDBCursorWithValue
_ = JSM GType
gTypeIDBCursorWithValue
  {-# INLINE typeGType #-}

noIDBCursorWithValue :: Maybe IDBCursorWithValue
noIDBCursorWithValue :: Maybe IDBCursorWithValue
noIDBCursorWithValue = Maybe IDBCursorWithValue
forall a. Maybe a
Nothing
{-# INLINE noIDBCursorWithValue #-}

gTypeIDBCursorWithValue :: JSM GType
gTypeIDBCursorWithValue :: JSM GType
gTypeIDBCursorWithValue = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBCursorWithValue"

-- | Functions for this inteface are in "JSDOM.IDBDatabase".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBDatabase Mozilla IDBDatabase documentation>
newtype IDBDatabase = IDBDatabase { IDBDatabase -> JSVal
unIDBDatabase :: JSVal }

instance PToJSVal IDBDatabase where
  pToJSVal :: IDBDatabase -> JSVal
pToJSVal = IDBDatabase -> JSVal
unIDBDatabase
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBDatabase where
  pFromJSVal :: JSVal -> IDBDatabase
pFromJSVal = JSVal -> IDBDatabase
IDBDatabase
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBDatabase where
  toJSVal :: IDBDatabase -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBDatabase -> JSVal) -> IDBDatabase -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBDatabase -> JSVal
unIDBDatabase
  {-# INLINE toJSVal #-}

instance FromJSVal IDBDatabase where
  fromJSVal :: JSVal -> JSM (Maybe IDBDatabase)
fromJSVal JSVal
v = (JSVal -> IDBDatabase) -> Maybe JSVal -> Maybe IDBDatabase
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBDatabase
IDBDatabase (Maybe JSVal -> Maybe IDBDatabase)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBDatabase)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBDatabase
fromJSValUnchecked = IDBDatabase -> JSM IDBDatabase
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBDatabase -> JSM IDBDatabase)
-> (JSVal -> IDBDatabase) -> JSVal -> JSM IDBDatabase
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBDatabase
IDBDatabase
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBDatabase where
  makeObject :: IDBDatabase -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBDatabase -> JSVal) -> IDBDatabase -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBDatabase -> JSVal
unIDBDatabase

instance IsEventTarget IDBDatabase
instance IsGObject IDBDatabase where
  typeGType :: IDBDatabase -> JSM GType
typeGType IDBDatabase
_ = JSM GType
gTypeIDBDatabase
  {-# INLINE typeGType #-}

noIDBDatabase :: Maybe IDBDatabase
noIDBDatabase :: Maybe IDBDatabase
noIDBDatabase = Maybe IDBDatabase
forall a. Maybe a
Nothing
{-# INLINE noIDBDatabase #-}

gTypeIDBDatabase :: JSM GType
gTypeIDBDatabase :: JSM GType
gTypeIDBDatabase = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBDatabase"

-- | Functions for this inteface are in "JSDOM.IDBFactory".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBFactory Mozilla IDBFactory documentation>
newtype IDBFactory = IDBFactory { IDBFactory -> JSVal
unIDBFactory :: JSVal }

instance PToJSVal IDBFactory where
  pToJSVal :: IDBFactory -> JSVal
pToJSVal = IDBFactory -> JSVal
unIDBFactory
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBFactory where
  pFromJSVal :: JSVal -> IDBFactory
pFromJSVal = JSVal -> IDBFactory
IDBFactory
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBFactory where
  toJSVal :: IDBFactory -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBFactory -> JSVal) -> IDBFactory -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBFactory -> JSVal
unIDBFactory
  {-# INLINE toJSVal #-}

instance FromJSVal IDBFactory where
  fromJSVal :: JSVal -> JSM (Maybe IDBFactory)
fromJSVal JSVal
v = (JSVal -> IDBFactory) -> Maybe JSVal -> Maybe IDBFactory
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBFactory
IDBFactory (Maybe JSVal -> Maybe IDBFactory)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBFactory)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBFactory
fromJSValUnchecked = IDBFactory -> JSM IDBFactory
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBFactory -> JSM IDBFactory)
-> (JSVal -> IDBFactory) -> JSVal -> JSM IDBFactory
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBFactory
IDBFactory
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBFactory where
  makeObject :: IDBFactory -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBFactory -> JSVal) -> IDBFactory -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBFactory -> JSVal
unIDBFactory

instance IsGObject IDBFactory where
  typeGType :: IDBFactory -> JSM GType
typeGType IDBFactory
_ = JSM GType
gTypeIDBFactory
  {-# INLINE typeGType #-}

noIDBFactory :: Maybe IDBFactory
noIDBFactory :: Maybe IDBFactory
noIDBFactory = Maybe IDBFactory
forall a. Maybe a
Nothing
{-# INLINE noIDBFactory #-}

gTypeIDBFactory :: JSM GType
gTypeIDBFactory :: JSM GType
gTypeIDBFactory = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBFactory"

-- | Functions for this inteface are in "JSDOM.IDBIndex".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBIndex Mozilla IDBIndex documentation>
newtype IDBIndex = IDBIndex { IDBIndex -> JSVal
unIDBIndex :: JSVal }

instance PToJSVal IDBIndex where
  pToJSVal :: IDBIndex -> JSVal
pToJSVal = IDBIndex -> JSVal
unIDBIndex
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBIndex where
  pFromJSVal :: JSVal -> IDBIndex
pFromJSVal = JSVal -> IDBIndex
IDBIndex
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBIndex where
  toJSVal :: IDBIndex -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBIndex -> JSVal) -> IDBIndex -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBIndex -> JSVal
unIDBIndex
  {-# INLINE toJSVal #-}

instance FromJSVal IDBIndex where
  fromJSVal :: JSVal -> JSM (Maybe IDBIndex)
fromJSVal JSVal
v = (JSVal -> IDBIndex) -> Maybe JSVal -> Maybe IDBIndex
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBIndex
IDBIndex (Maybe JSVal -> Maybe IDBIndex)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBIndex
fromJSValUnchecked = IDBIndex -> JSM IDBIndex
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBIndex -> JSM IDBIndex)
-> (JSVal -> IDBIndex) -> JSVal -> JSM IDBIndex
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBIndex
IDBIndex
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBIndex where
  makeObject :: IDBIndex -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBIndex -> JSVal) -> IDBIndex -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBIndex -> JSVal
unIDBIndex

instance IsGObject IDBIndex where
  typeGType :: IDBIndex -> JSM GType
typeGType IDBIndex
_ = JSM GType
gTypeIDBIndex
  {-# INLINE typeGType #-}

noIDBIndex :: Maybe IDBIndex
noIDBIndex :: Maybe IDBIndex
noIDBIndex = Maybe IDBIndex
forall a. Maybe a
Nothing
{-# INLINE noIDBIndex #-}

gTypeIDBIndex :: JSM GType
gTypeIDBIndex :: JSM GType
gTypeIDBIndex = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBIndex"

-- | Functions for this inteface are in "JSDOM.IDBIndexParameters".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBIndexParameters Mozilla IDBIndexParameters documentation>
newtype IDBIndexParameters = IDBIndexParameters { IDBIndexParameters -> JSVal
unIDBIndexParameters :: JSVal }

instance PToJSVal IDBIndexParameters where
  pToJSVal :: IDBIndexParameters -> JSVal
pToJSVal = IDBIndexParameters -> JSVal
unIDBIndexParameters
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBIndexParameters where
  pFromJSVal :: JSVal -> IDBIndexParameters
pFromJSVal = JSVal -> IDBIndexParameters
IDBIndexParameters
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBIndexParameters where
  toJSVal :: IDBIndexParameters -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBIndexParameters -> JSVal) -> IDBIndexParameters -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBIndexParameters -> JSVal
unIDBIndexParameters
  {-# INLINE toJSVal #-}

instance FromJSVal IDBIndexParameters where
  fromJSVal :: JSVal -> JSM (Maybe IDBIndexParameters)
fromJSVal JSVal
v = (JSVal -> IDBIndexParameters)
-> Maybe JSVal -> Maybe IDBIndexParameters
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBIndexParameters
IDBIndexParameters (Maybe JSVal -> Maybe IDBIndexParameters)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBIndexParameters)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBIndexParameters
fromJSValUnchecked = IDBIndexParameters -> JSM IDBIndexParameters
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBIndexParameters -> JSM IDBIndexParameters)
-> (JSVal -> IDBIndexParameters) -> JSVal -> JSM IDBIndexParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBIndexParameters
IDBIndexParameters
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBIndexParameters where
  makeObject :: IDBIndexParameters -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBIndexParameters -> JSVal)
-> IDBIndexParameters
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBIndexParameters -> JSVal
unIDBIndexParameters

instance IsGObject IDBIndexParameters where
  typeGType :: IDBIndexParameters -> JSM GType
typeGType IDBIndexParameters
_ = JSM GType
gTypeIDBIndexParameters
  {-# INLINE typeGType #-}

noIDBIndexParameters :: Maybe IDBIndexParameters
noIDBIndexParameters :: Maybe IDBIndexParameters
noIDBIndexParameters = Maybe IDBIndexParameters
forall a. Maybe a
Nothing
{-# INLINE noIDBIndexParameters #-}

gTypeIDBIndexParameters :: JSM GType
gTypeIDBIndexParameters :: JSM GType
gTypeIDBIndexParameters = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBIndexParameters"

-- | Functions for this inteface are in "JSDOM.IDBKeyRange".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBKeyRange Mozilla IDBKeyRange documentation>
newtype IDBKeyRange = IDBKeyRange { IDBKeyRange -> JSVal
unIDBKeyRange :: JSVal }

instance PToJSVal IDBKeyRange where
  pToJSVal :: IDBKeyRange -> JSVal
pToJSVal = IDBKeyRange -> JSVal
unIDBKeyRange
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBKeyRange where
  pFromJSVal :: JSVal -> IDBKeyRange
pFromJSVal = JSVal -> IDBKeyRange
IDBKeyRange
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBKeyRange where
  toJSVal :: IDBKeyRange -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBKeyRange -> JSVal) -> IDBKeyRange -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBKeyRange -> JSVal
unIDBKeyRange
  {-# INLINE toJSVal #-}

instance FromJSVal IDBKeyRange where
  fromJSVal :: JSVal -> JSM (Maybe IDBKeyRange)
fromJSVal JSVal
v = (JSVal -> IDBKeyRange) -> Maybe JSVal -> Maybe IDBKeyRange
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBKeyRange
IDBKeyRange (Maybe JSVal -> Maybe IDBKeyRange)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBKeyRange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBKeyRange
fromJSValUnchecked = IDBKeyRange -> JSM IDBKeyRange
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBKeyRange -> JSM IDBKeyRange)
-> (JSVal -> IDBKeyRange) -> JSVal -> JSM IDBKeyRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBKeyRange
IDBKeyRange
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBKeyRange where
  makeObject :: IDBKeyRange -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBKeyRange -> JSVal) -> IDBKeyRange -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBKeyRange -> JSVal
unIDBKeyRange

instance IsGObject IDBKeyRange where
  typeGType :: IDBKeyRange -> JSM GType
typeGType IDBKeyRange
_ = JSM GType
gTypeIDBKeyRange
  {-# INLINE typeGType #-}

noIDBKeyRange :: Maybe IDBKeyRange
noIDBKeyRange :: Maybe IDBKeyRange
noIDBKeyRange = Maybe IDBKeyRange
forall a. Maybe a
Nothing
{-# INLINE noIDBKeyRange #-}

gTypeIDBKeyRange :: JSM GType
gTypeIDBKeyRange :: JSM GType
gTypeIDBKeyRange = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBKeyRange"

-- | Functions for this inteface are in "JSDOM.IDBObjectStore".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore Mozilla IDBObjectStore documentation>
newtype IDBObjectStore = IDBObjectStore { IDBObjectStore -> JSVal
unIDBObjectStore :: JSVal }

instance PToJSVal IDBObjectStore where
  pToJSVal :: IDBObjectStore -> JSVal
pToJSVal = IDBObjectStore -> JSVal
unIDBObjectStore
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBObjectStore where
  pFromJSVal :: JSVal -> IDBObjectStore
pFromJSVal = JSVal -> IDBObjectStore
IDBObjectStore
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBObjectStore where
  toJSVal :: IDBObjectStore -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBObjectStore -> JSVal) -> IDBObjectStore -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBObjectStore -> JSVal
unIDBObjectStore
  {-# INLINE toJSVal #-}

instance FromJSVal IDBObjectStore where
  fromJSVal :: JSVal -> JSM (Maybe IDBObjectStore)
fromJSVal JSVal
v = (JSVal -> IDBObjectStore) -> Maybe JSVal -> Maybe IDBObjectStore
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBObjectStore
IDBObjectStore (Maybe JSVal -> Maybe IDBObjectStore)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBObjectStore)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBObjectStore
fromJSValUnchecked = IDBObjectStore -> JSM IDBObjectStore
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBObjectStore -> JSM IDBObjectStore)
-> (JSVal -> IDBObjectStore) -> JSVal -> JSM IDBObjectStore
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBObjectStore
IDBObjectStore
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBObjectStore where
  makeObject :: IDBObjectStore -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBObjectStore -> JSVal) -> IDBObjectStore -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBObjectStore -> JSVal
unIDBObjectStore

instance IsGObject IDBObjectStore where
  typeGType :: IDBObjectStore -> JSM GType
typeGType IDBObjectStore
_ = JSM GType
gTypeIDBObjectStore
  {-# INLINE typeGType #-}

noIDBObjectStore :: Maybe IDBObjectStore
noIDBObjectStore :: Maybe IDBObjectStore
noIDBObjectStore = Maybe IDBObjectStore
forall a. Maybe a
Nothing
{-# INLINE noIDBObjectStore #-}

gTypeIDBObjectStore :: JSM GType
gTypeIDBObjectStore :: JSM GType
gTypeIDBObjectStore = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBObjectStore"

-- | Functions for this inteface are in "JSDOM.IDBObjectStoreParameters".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStoreParameters Mozilla IDBObjectStoreParameters documentation>
newtype IDBObjectStoreParameters = IDBObjectStoreParameters { IDBObjectStoreParameters -> JSVal
unIDBObjectStoreParameters :: JSVal }

instance PToJSVal IDBObjectStoreParameters where
  pToJSVal :: IDBObjectStoreParameters -> JSVal
pToJSVal = IDBObjectStoreParameters -> JSVal
unIDBObjectStoreParameters
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBObjectStoreParameters where
  pFromJSVal :: JSVal -> IDBObjectStoreParameters
pFromJSVal = JSVal -> IDBObjectStoreParameters
IDBObjectStoreParameters
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBObjectStoreParameters where
  toJSVal :: IDBObjectStoreParameters -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBObjectStoreParameters -> JSVal)
-> IDBObjectStoreParameters
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBObjectStoreParameters -> JSVal
unIDBObjectStoreParameters
  {-# INLINE toJSVal #-}

instance FromJSVal IDBObjectStoreParameters where
  fromJSVal :: JSVal -> JSM (Maybe IDBObjectStoreParameters)
fromJSVal JSVal
v = (JSVal -> IDBObjectStoreParameters)
-> Maybe JSVal -> Maybe IDBObjectStoreParameters
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBObjectStoreParameters
IDBObjectStoreParameters (Maybe JSVal -> Maybe IDBObjectStoreParameters)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBObjectStoreParameters)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBObjectStoreParameters
fromJSValUnchecked = IDBObjectStoreParameters -> JSM IDBObjectStoreParameters
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBObjectStoreParameters -> JSM IDBObjectStoreParameters)
-> (JSVal -> IDBObjectStoreParameters)
-> JSVal
-> JSM IDBObjectStoreParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBObjectStoreParameters
IDBObjectStoreParameters
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBObjectStoreParameters where
  makeObject :: IDBObjectStoreParameters -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBObjectStoreParameters -> JSVal)
-> IDBObjectStoreParameters
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBObjectStoreParameters -> JSVal
unIDBObjectStoreParameters

instance IsGObject IDBObjectStoreParameters where
  typeGType :: IDBObjectStoreParameters -> JSM GType
typeGType IDBObjectStoreParameters
_ = JSM GType
gTypeIDBObjectStoreParameters
  {-# INLINE typeGType #-}

noIDBObjectStoreParameters :: Maybe IDBObjectStoreParameters
noIDBObjectStoreParameters :: Maybe IDBObjectStoreParameters
noIDBObjectStoreParameters = Maybe IDBObjectStoreParameters
forall a. Maybe a
Nothing
{-# INLINE noIDBObjectStoreParameters #-}

gTypeIDBObjectStoreParameters :: JSM GType
gTypeIDBObjectStoreParameters :: JSM GType
gTypeIDBObjectStoreParameters = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBObjectStoreParameters"

-- | Functions for this inteface are in "JSDOM.IDBOpenDBRequest".
-- Base interface functions are in:
--
--     * "JSDOM.IDBRequest"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBOpenDBRequest Mozilla IDBOpenDBRequest documentation>
newtype IDBOpenDBRequest = IDBOpenDBRequest { IDBOpenDBRequest -> JSVal
unIDBOpenDBRequest :: JSVal }

instance PToJSVal IDBOpenDBRequest where
  pToJSVal :: IDBOpenDBRequest -> JSVal
pToJSVal = IDBOpenDBRequest -> JSVal
unIDBOpenDBRequest
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBOpenDBRequest where
  pFromJSVal :: JSVal -> IDBOpenDBRequest
pFromJSVal = JSVal -> IDBOpenDBRequest
IDBOpenDBRequest
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBOpenDBRequest where
  toJSVal :: IDBOpenDBRequest -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBOpenDBRequest -> JSVal) -> IDBOpenDBRequest -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBOpenDBRequest -> JSVal
unIDBOpenDBRequest
  {-# INLINE toJSVal #-}

instance FromJSVal IDBOpenDBRequest where
  fromJSVal :: JSVal -> JSM (Maybe IDBOpenDBRequest)
fromJSVal JSVal
v = (JSVal -> IDBOpenDBRequest)
-> Maybe JSVal -> Maybe IDBOpenDBRequest
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBOpenDBRequest
IDBOpenDBRequest (Maybe JSVal -> Maybe IDBOpenDBRequest)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBOpenDBRequest)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBOpenDBRequest
fromJSValUnchecked = IDBOpenDBRequest -> JSM IDBOpenDBRequest
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBOpenDBRequest -> JSM IDBOpenDBRequest)
-> (JSVal -> IDBOpenDBRequest) -> JSVal -> JSM IDBOpenDBRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBOpenDBRequest
IDBOpenDBRequest
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBOpenDBRequest where
  makeObject :: IDBOpenDBRequest -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBOpenDBRequest -> JSVal) -> IDBOpenDBRequest -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBOpenDBRequest -> JSVal
unIDBOpenDBRequest

instance IsIDBRequest IDBOpenDBRequest
instance IsEventTarget IDBOpenDBRequest
instance IsGObject IDBOpenDBRequest where
  typeGType :: IDBOpenDBRequest -> JSM GType
typeGType IDBOpenDBRequest
_ = JSM GType
gTypeIDBOpenDBRequest
  {-# INLINE typeGType #-}

noIDBOpenDBRequest :: Maybe IDBOpenDBRequest
noIDBOpenDBRequest :: Maybe IDBOpenDBRequest
noIDBOpenDBRequest = Maybe IDBOpenDBRequest
forall a. Maybe a
Nothing
{-# INLINE noIDBOpenDBRequest #-}

gTypeIDBOpenDBRequest :: JSM GType
gTypeIDBOpenDBRequest :: JSM GType
gTypeIDBOpenDBRequest = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBOpenDBRequest"

-- | Functions for this inteface are in "JSDOM.IDBRequest".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBRequest Mozilla IDBRequest documentation>
newtype IDBRequest = IDBRequest { IDBRequest -> JSVal
unIDBRequest :: JSVal }

instance PToJSVal IDBRequest where
  pToJSVal :: IDBRequest -> JSVal
pToJSVal = IDBRequest -> JSVal
unIDBRequest
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBRequest where
  pFromJSVal :: JSVal -> IDBRequest
pFromJSVal = JSVal -> IDBRequest
IDBRequest
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBRequest where
  toJSVal :: IDBRequest -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBRequest -> JSVal) -> IDBRequest -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBRequest -> JSVal
unIDBRequest
  {-# INLINE toJSVal #-}

instance FromJSVal IDBRequest where
  fromJSVal :: JSVal -> JSM (Maybe IDBRequest)
fromJSVal JSVal
v = (JSVal -> IDBRequest) -> Maybe JSVal -> Maybe IDBRequest
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBRequest
IDBRequest (Maybe JSVal -> Maybe IDBRequest)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBRequest)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBRequest
fromJSValUnchecked = IDBRequest -> JSM IDBRequest
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBRequest -> JSM IDBRequest)
-> (JSVal -> IDBRequest) -> JSVal -> JSM IDBRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBRequest
IDBRequest
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBRequest where
  makeObject :: IDBRequest -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBRequest -> JSVal) -> IDBRequest -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBRequest -> JSVal
unIDBRequest

class (IsEventTarget o, IsGObject o) => IsIDBRequest o
toIDBRequest :: IsIDBRequest o => o -> IDBRequest
toIDBRequest :: forall o. IsIDBRequest o => o -> IDBRequest
toIDBRequest = JSVal -> IDBRequest
IDBRequest (JSVal -> IDBRequest) -> (o -> JSVal) -> o -> IDBRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsIDBRequest IDBRequest
instance IsEventTarget IDBRequest
instance IsGObject IDBRequest where
  typeGType :: IDBRequest -> JSM GType
typeGType IDBRequest
_ = JSM GType
gTypeIDBRequest
  {-# INLINE typeGType #-}

noIDBRequest :: Maybe IDBRequest
noIDBRequest :: Maybe IDBRequest
noIDBRequest = Maybe IDBRequest
forall a. Maybe a
Nothing
{-# INLINE noIDBRequest #-}

gTypeIDBRequest :: JSM GType
gTypeIDBRequest :: JSM GType
gTypeIDBRequest = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBRequest"

-- | Functions for this inteface are in "JSDOM.IDBTransaction".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBTransaction Mozilla IDBTransaction documentation>
newtype IDBTransaction = IDBTransaction { IDBTransaction -> JSVal
unIDBTransaction :: JSVal }

instance PToJSVal IDBTransaction where
  pToJSVal :: IDBTransaction -> JSVal
pToJSVal = IDBTransaction -> JSVal
unIDBTransaction
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBTransaction where
  pFromJSVal :: JSVal -> IDBTransaction
pFromJSVal = JSVal -> IDBTransaction
IDBTransaction
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBTransaction where
  toJSVal :: IDBTransaction -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBTransaction -> JSVal) -> IDBTransaction -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBTransaction -> JSVal
unIDBTransaction
  {-# INLINE toJSVal #-}

instance FromJSVal IDBTransaction where
  fromJSVal :: JSVal -> JSM (Maybe IDBTransaction)
fromJSVal JSVal
v = (JSVal -> IDBTransaction) -> Maybe JSVal -> Maybe IDBTransaction
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBTransaction
IDBTransaction (Maybe JSVal -> Maybe IDBTransaction)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBTransaction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBTransaction
fromJSValUnchecked = IDBTransaction -> JSM IDBTransaction
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBTransaction -> JSM IDBTransaction)
-> (JSVal -> IDBTransaction) -> JSVal -> JSM IDBTransaction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBTransaction
IDBTransaction
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBTransaction where
  makeObject :: IDBTransaction -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBTransaction -> JSVal) -> IDBTransaction -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBTransaction -> JSVal
unIDBTransaction

instance IsEventTarget IDBTransaction
instance IsGObject IDBTransaction where
  typeGType :: IDBTransaction -> JSM GType
typeGType IDBTransaction
_ = JSM GType
gTypeIDBTransaction
  {-# INLINE typeGType #-}

noIDBTransaction :: Maybe IDBTransaction
noIDBTransaction :: Maybe IDBTransaction
noIDBTransaction = Maybe IDBTransaction
forall a. Maybe a
Nothing
{-# INLINE noIDBTransaction #-}

gTypeIDBTransaction :: JSM GType
gTypeIDBTransaction :: JSM GType
gTypeIDBTransaction = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBTransaction"

-- | Functions for this inteface are in "JSDOM.IDBVersionChangeEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBVersionChangeEvent Mozilla IDBVersionChangeEvent documentation>
newtype IDBVersionChangeEvent = IDBVersionChangeEvent { IDBVersionChangeEvent -> JSVal
unIDBVersionChangeEvent :: JSVal }

instance PToJSVal IDBVersionChangeEvent where
  pToJSVal :: IDBVersionChangeEvent -> JSVal
pToJSVal = IDBVersionChangeEvent -> JSVal
unIDBVersionChangeEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBVersionChangeEvent where
  pFromJSVal :: JSVal -> IDBVersionChangeEvent
pFromJSVal = JSVal -> IDBVersionChangeEvent
IDBVersionChangeEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBVersionChangeEvent where
  toJSVal :: IDBVersionChangeEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBVersionChangeEvent -> JSVal)
-> IDBVersionChangeEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBVersionChangeEvent -> JSVal
unIDBVersionChangeEvent
  {-# INLINE toJSVal #-}

instance FromJSVal IDBVersionChangeEvent where
  fromJSVal :: JSVal -> JSM (Maybe IDBVersionChangeEvent)
fromJSVal JSVal
v = (JSVal -> IDBVersionChangeEvent)
-> Maybe JSVal -> Maybe IDBVersionChangeEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBVersionChangeEvent
IDBVersionChangeEvent (Maybe JSVal -> Maybe IDBVersionChangeEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBVersionChangeEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBVersionChangeEvent
fromJSValUnchecked = IDBVersionChangeEvent -> JSM IDBVersionChangeEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBVersionChangeEvent -> JSM IDBVersionChangeEvent)
-> (JSVal -> IDBVersionChangeEvent)
-> JSVal
-> JSM IDBVersionChangeEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBVersionChangeEvent
IDBVersionChangeEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBVersionChangeEvent where
  makeObject :: IDBVersionChangeEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBVersionChangeEvent -> JSVal)
-> IDBVersionChangeEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBVersionChangeEvent -> JSVal
unIDBVersionChangeEvent

instance IsEvent IDBVersionChangeEvent
instance IsGObject IDBVersionChangeEvent where
  typeGType :: IDBVersionChangeEvent -> JSM GType
typeGType IDBVersionChangeEvent
_ = JSM GType
gTypeIDBVersionChangeEvent
  {-# INLINE typeGType #-}

noIDBVersionChangeEvent :: Maybe IDBVersionChangeEvent
noIDBVersionChangeEvent :: Maybe IDBVersionChangeEvent
noIDBVersionChangeEvent = Maybe IDBVersionChangeEvent
forall a. Maybe a
Nothing
{-# INLINE noIDBVersionChangeEvent #-}

gTypeIDBVersionChangeEvent :: JSM GType
gTypeIDBVersionChangeEvent :: JSM GType
gTypeIDBVersionChangeEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBVersionChangeEvent"

-- | Functions for this inteface are in "JSDOM.IDBVersionChangeEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IDBVersionChangeEventInit Mozilla IDBVersionChangeEventInit documentation>
newtype IDBVersionChangeEventInit = IDBVersionChangeEventInit { IDBVersionChangeEventInit -> JSVal
unIDBVersionChangeEventInit :: JSVal }

instance PToJSVal IDBVersionChangeEventInit where
  pToJSVal :: IDBVersionChangeEventInit -> JSVal
pToJSVal = IDBVersionChangeEventInit -> JSVal
unIDBVersionChangeEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal IDBVersionChangeEventInit where
  pFromJSVal :: JSVal -> IDBVersionChangeEventInit
pFromJSVal = JSVal -> IDBVersionChangeEventInit
IDBVersionChangeEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal IDBVersionChangeEventInit where
  toJSVal :: IDBVersionChangeEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IDBVersionChangeEventInit -> JSVal)
-> IDBVersionChangeEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBVersionChangeEventInit -> JSVal
unIDBVersionChangeEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal IDBVersionChangeEventInit where
  fromJSVal :: JSVal -> JSM (Maybe IDBVersionChangeEventInit)
fromJSVal JSVal
v = (JSVal -> IDBVersionChangeEventInit)
-> Maybe JSVal -> Maybe IDBVersionChangeEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IDBVersionChangeEventInit
IDBVersionChangeEventInit (Maybe JSVal -> Maybe IDBVersionChangeEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe IDBVersionChangeEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IDBVersionChangeEventInit
fromJSValUnchecked = IDBVersionChangeEventInit -> JSM IDBVersionChangeEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBVersionChangeEventInit -> JSM IDBVersionChangeEventInit)
-> (JSVal -> IDBVersionChangeEventInit)
-> JSVal
-> JSM IDBVersionChangeEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IDBVersionChangeEventInit
IDBVersionChangeEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IDBVersionChangeEventInit where
  makeObject :: IDBVersionChangeEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IDBVersionChangeEventInit -> JSVal)
-> IDBVersionChangeEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IDBVersionChangeEventInit -> JSVal
unIDBVersionChangeEventInit

instance IsEventInit IDBVersionChangeEventInit
instance IsGObject IDBVersionChangeEventInit where
  typeGType :: IDBVersionChangeEventInit -> JSM GType
typeGType IDBVersionChangeEventInit
_ = JSM GType
gTypeIDBVersionChangeEventInit
  {-# INLINE typeGType #-}

noIDBVersionChangeEventInit :: Maybe IDBVersionChangeEventInit
noIDBVersionChangeEventInit :: Maybe IDBVersionChangeEventInit
noIDBVersionChangeEventInit = Maybe IDBVersionChangeEventInit
forall a. Maybe a
Nothing
{-# INLINE noIDBVersionChangeEventInit #-}

gTypeIDBVersionChangeEventInit :: JSM GType
gTypeIDBVersionChangeEventInit :: JSM GType
gTypeIDBVersionChangeEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IDBVersionChangeEventInit"

-- | Functions for this inteface are in "JSDOM.ImageData".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ImageData Mozilla ImageData documentation>
newtype ImageData = ImageData { ImageData -> JSVal
unImageData :: JSVal }

instance PToJSVal ImageData where
  pToJSVal :: ImageData -> JSVal
pToJSVal = ImageData -> JSVal
unImageData
  {-# INLINE pToJSVal #-}

instance PFromJSVal ImageData where
  pFromJSVal :: JSVal -> ImageData
pFromJSVal = JSVal -> ImageData
ImageData
  {-# INLINE pFromJSVal #-}

instance ToJSVal ImageData where
  toJSVal :: ImageData -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ImageData -> JSVal) -> ImageData -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImageData -> JSVal
unImageData
  {-# INLINE toJSVal #-}

instance FromJSVal ImageData where
  fromJSVal :: JSVal -> JSM (Maybe ImageData)
fromJSVal JSVal
v = (JSVal -> ImageData) -> Maybe JSVal -> Maybe ImageData
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ImageData
ImageData (Maybe JSVal -> Maybe ImageData)
-> JSM (Maybe JSVal) -> JSM (Maybe ImageData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ImageData
fromJSValUnchecked = ImageData -> JSM ImageData
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ImageData -> JSM ImageData)
-> (JSVal -> ImageData) -> JSVal -> JSM ImageData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ImageData
ImageData
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ImageData where
  makeObject :: ImageData -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ImageData -> JSVal) -> ImageData -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImageData -> JSVal
unImageData

instance IsGObject ImageData where
  typeGType :: ImageData -> JSM GType
typeGType ImageData
_ = JSM GType
gTypeImageData
  {-# INLINE typeGType #-}

noImageData :: Maybe ImageData
noImageData :: Maybe ImageData
noImageData = Maybe ImageData
forall a. Maybe a
Nothing
{-# INLINE noImageData #-}

gTypeImageData :: JSM GType
gTypeImageData :: JSM GType
gTypeImageData = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ImageData"

-- | Functions for this inteface are in "JSDOM.InputEvent".
-- Base interface functions are in:
--
--     * "JSDOM.UIEvent"
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/InputEvent Mozilla InputEvent documentation>
newtype InputEvent = InputEvent { InputEvent -> JSVal
unInputEvent :: JSVal }

instance PToJSVal InputEvent where
  pToJSVal :: InputEvent -> JSVal
pToJSVal = InputEvent -> JSVal
unInputEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal InputEvent where
  pFromJSVal :: JSVal -> InputEvent
pFromJSVal = JSVal -> InputEvent
InputEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal InputEvent where
  toJSVal :: InputEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (InputEvent -> JSVal) -> InputEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputEvent -> JSVal
unInputEvent
  {-# INLINE toJSVal #-}

instance FromJSVal InputEvent where
  fromJSVal :: JSVal -> JSM (Maybe InputEvent)
fromJSVal JSVal
v = (JSVal -> InputEvent) -> Maybe JSVal -> Maybe InputEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> InputEvent
InputEvent (Maybe JSVal -> Maybe InputEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe InputEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM InputEvent
fromJSValUnchecked = InputEvent -> JSM InputEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (InputEvent -> JSM InputEvent)
-> (JSVal -> InputEvent) -> JSVal -> JSM InputEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> InputEvent
InputEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject InputEvent where
  makeObject :: InputEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (InputEvent -> JSVal) -> InputEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputEvent -> JSVal
unInputEvent

instance IsUIEvent InputEvent
instance IsEvent InputEvent
instance IsGObject InputEvent where
  typeGType :: InputEvent -> JSM GType
typeGType InputEvent
_ = JSM GType
gTypeInputEvent
  {-# INLINE typeGType #-}

noInputEvent :: Maybe InputEvent
noInputEvent :: Maybe InputEvent
noInputEvent = Maybe InputEvent
forall a. Maybe a
Nothing
{-# INLINE noInputEvent #-}

gTypeInputEvent :: JSM GType
gTypeInputEvent :: JSM GType
gTypeInputEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"InputEvent"

-- | Functions for this inteface are in "JSDOM.InputEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.UIEventInit"
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/InputEventInit Mozilla InputEventInit documentation>
newtype InputEventInit = InputEventInit { InputEventInit -> JSVal
unInputEventInit :: JSVal }

instance PToJSVal InputEventInit where
  pToJSVal :: InputEventInit -> JSVal
pToJSVal = InputEventInit -> JSVal
unInputEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal InputEventInit where
  pFromJSVal :: JSVal -> InputEventInit
pFromJSVal = JSVal -> InputEventInit
InputEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal InputEventInit where
  toJSVal :: InputEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (InputEventInit -> JSVal) -> InputEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputEventInit -> JSVal
unInputEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal InputEventInit where
  fromJSVal :: JSVal -> JSM (Maybe InputEventInit)
fromJSVal JSVal
v = (JSVal -> InputEventInit) -> Maybe JSVal -> Maybe InputEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> InputEventInit
InputEventInit (Maybe JSVal -> Maybe InputEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe InputEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM InputEventInit
fromJSValUnchecked = InputEventInit -> JSM InputEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (InputEventInit -> JSM InputEventInit)
-> (JSVal -> InputEventInit) -> JSVal -> JSM InputEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> InputEventInit
InputEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject InputEventInit where
  makeObject :: InputEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (InputEventInit -> JSVal) -> InputEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputEventInit -> JSVal
unInputEventInit

instance IsUIEventInit InputEventInit
instance IsEventInit InputEventInit
instance IsGObject InputEventInit where
  typeGType :: InputEventInit -> JSM GType
typeGType InputEventInit
_ = JSM GType
gTypeInputEventInit
  {-# INLINE typeGType #-}

noInputEventInit :: Maybe InputEventInit
noInputEventInit :: Maybe InputEventInit
noInputEventInit = Maybe InputEventInit
forall a. Maybe a
Nothing
{-# INLINE noInputEventInit #-}

gTypeInputEventInit :: JSM GType
gTypeInputEventInit :: JSM GType
gTypeInputEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"InputEventInit"

-- | Functions for this inteface are in "JSDOM.InspectorFrontendHost".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/InspectorFrontendHost Mozilla InspectorFrontendHost documentation>
newtype InspectorFrontendHost = InspectorFrontendHost { InspectorFrontendHost -> JSVal
unInspectorFrontendHost :: JSVal }

instance PToJSVal InspectorFrontendHost where
  pToJSVal :: InspectorFrontendHost -> JSVal
pToJSVal = InspectorFrontendHost -> JSVal
unInspectorFrontendHost
  {-# INLINE pToJSVal #-}

instance PFromJSVal InspectorFrontendHost where
  pFromJSVal :: JSVal -> InspectorFrontendHost
pFromJSVal = JSVal -> InspectorFrontendHost
InspectorFrontendHost
  {-# INLINE pFromJSVal #-}

instance ToJSVal InspectorFrontendHost where
  toJSVal :: InspectorFrontendHost -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (InspectorFrontendHost -> JSVal)
-> InspectorFrontendHost
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InspectorFrontendHost -> JSVal
unInspectorFrontendHost
  {-# INLINE toJSVal #-}

instance FromJSVal InspectorFrontendHost where
  fromJSVal :: JSVal -> JSM (Maybe InspectorFrontendHost)
fromJSVal JSVal
v = (JSVal -> InspectorFrontendHost)
-> Maybe JSVal -> Maybe InspectorFrontendHost
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> InspectorFrontendHost
InspectorFrontendHost (Maybe JSVal -> Maybe InspectorFrontendHost)
-> JSM (Maybe JSVal) -> JSM (Maybe InspectorFrontendHost)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM InspectorFrontendHost
fromJSValUnchecked = InspectorFrontendHost -> JSM InspectorFrontendHost
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (InspectorFrontendHost -> JSM InspectorFrontendHost)
-> (JSVal -> InspectorFrontendHost)
-> JSVal
-> JSM InspectorFrontendHost
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> InspectorFrontendHost
InspectorFrontendHost
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject InspectorFrontendHost where
  makeObject :: InspectorFrontendHost -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (InspectorFrontendHost -> JSVal)
-> InspectorFrontendHost
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InspectorFrontendHost -> JSVal
unInspectorFrontendHost

instance IsGObject InspectorFrontendHost where
  typeGType :: InspectorFrontendHost -> JSM GType
typeGType InspectorFrontendHost
_ = JSM GType
gTypeInspectorFrontendHost
  {-# INLINE typeGType #-}

noInspectorFrontendHost :: Maybe InspectorFrontendHost
noInspectorFrontendHost :: Maybe InspectorFrontendHost
noInspectorFrontendHost = Maybe InspectorFrontendHost
forall a. Maybe a
Nothing
{-# INLINE noInspectorFrontendHost #-}

gTypeInspectorFrontendHost :: JSM GType
gTypeInspectorFrontendHost :: JSM GType
gTypeInspectorFrontendHost = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"InspectorFrontendHost"

-- | Functions for this inteface are in "JSDOM.IntersectionObserver".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IntersectionObserver Mozilla IntersectionObserver documentation>
newtype IntersectionObserver = IntersectionObserver { IntersectionObserver -> JSVal
unIntersectionObserver :: JSVal }

instance PToJSVal IntersectionObserver where
  pToJSVal :: IntersectionObserver -> JSVal
pToJSVal = IntersectionObserver -> JSVal
unIntersectionObserver
  {-# INLINE pToJSVal #-}

instance PFromJSVal IntersectionObserver where
  pFromJSVal :: JSVal -> IntersectionObserver
pFromJSVal = JSVal -> IntersectionObserver
IntersectionObserver
  {-# INLINE pFromJSVal #-}

instance ToJSVal IntersectionObserver where
  toJSVal :: IntersectionObserver -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IntersectionObserver -> JSVal)
-> IntersectionObserver
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntersectionObserver -> JSVal
unIntersectionObserver
  {-# INLINE toJSVal #-}

instance FromJSVal IntersectionObserver where
  fromJSVal :: JSVal -> JSM (Maybe IntersectionObserver)
fromJSVal JSVal
v = (JSVal -> IntersectionObserver)
-> Maybe JSVal -> Maybe IntersectionObserver
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IntersectionObserver
IntersectionObserver (Maybe JSVal -> Maybe IntersectionObserver)
-> JSM (Maybe JSVal) -> JSM (Maybe IntersectionObserver)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IntersectionObserver
fromJSValUnchecked = IntersectionObserver -> JSM IntersectionObserver
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IntersectionObserver -> JSM IntersectionObserver)
-> (JSVal -> IntersectionObserver)
-> JSVal
-> JSM IntersectionObserver
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IntersectionObserver
IntersectionObserver
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IntersectionObserver where
  makeObject :: IntersectionObserver -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IntersectionObserver -> JSVal)
-> IntersectionObserver
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntersectionObserver -> JSVal
unIntersectionObserver

instance IsGObject IntersectionObserver where
  typeGType :: IntersectionObserver -> JSM GType
typeGType IntersectionObserver
_ = JSM GType
gTypeIntersectionObserver
  {-# INLINE typeGType #-}

noIntersectionObserver :: Maybe IntersectionObserver
noIntersectionObserver :: Maybe IntersectionObserver
noIntersectionObserver = Maybe IntersectionObserver
forall a. Maybe a
Nothing
{-# INLINE noIntersectionObserver #-}

gTypeIntersectionObserver :: JSM GType
gTypeIntersectionObserver :: JSM GType
gTypeIntersectionObserver = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IntersectionObserver"

-- | Functions for this inteface are in "JSDOM.IntersectionObserverEntry".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IntersectionObserverEntry Mozilla IntersectionObserverEntry documentation>
newtype IntersectionObserverEntry = IntersectionObserverEntry { IntersectionObserverEntry -> JSVal
unIntersectionObserverEntry :: JSVal }

instance PToJSVal IntersectionObserverEntry where
  pToJSVal :: IntersectionObserverEntry -> JSVal
pToJSVal = IntersectionObserverEntry -> JSVal
unIntersectionObserverEntry
  {-# INLINE pToJSVal #-}

instance PFromJSVal IntersectionObserverEntry where
  pFromJSVal :: JSVal -> IntersectionObserverEntry
pFromJSVal = JSVal -> IntersectionObserverEntry
IntersectionObserverEntry
  {-# INLINE pFromJSVal #-}

instance ToJSVal IntersectionObserverEntry where
  toJSVal :: IntersectionObserverEntry -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IntersectionObserverEntry -> JSVal)
-> IntersectionObserverEntry
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntersectionObserverEntry -> JSVal
unIntersectionObserverEntry
  {-# INLINE toJSVal #-}

instance FromJSVal IntersectionObserverEntry where
  fromJSVal :: JSVal -> JSM (Maybe IntersectionObserverEntry)
fromJSVal JSVal
v = (JSVal -> IntersectionObserverEntry)
-> Maybe JSVal -> Maybe IntersectionObserverEntry
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IntersectionObserverEntry
IntersectionObserverEntry (Maybe JSVal -> Maybe IntersectionObserverEntry)
-> JSM (Maybe JSVal) -> JSM (Maybe IntersectionObserverEntry)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IntersectionObserverEntry
fromJSValUnchecked = IntersectionObserverEntry -> JSM IntersectionObserverEntry
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IntersectionObserverEntry -> JSM IntersectionObserverEntry)
-> (JSVal -> IntersectionObserverEntry)
-> JSVal
-> JSM IntersectionObserverEntry
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IntersectionObserverEntry
IntersectionObserverEntry
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IntersectionObserverEntry where
  makeObject :: IntersectionObserverEntry -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IntersectionObserverEntry -> JSVal)
-> IntersectionObserverEntry
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntersectionObserverEntry -> JSVal
unIntersectionObserverEntry

instance IsGObject IntersectionObserverEntry where
  typeGType :: IntersectionObserverEntry -> JSM GType
typeGType IntersectionObserverEntry
_ = JSM GType
gTypeIntersectionObserverEntry
  {-# INLINE typeGType #-}

noIntersectionObserverEntry :: Maybe IntersectionObserverEntry
noIntersectionObserverEntry :: Maybe IntersectionObserverEntry
noIntersectionObserverEntry = Maybe IntersectionObserverEntry
forall a. Maybe a
Nothing
{-# INLINE noIntersectionObserverEntry #-}

gTypeIntersectionObserverEntry :: JSM GType
gTypeIntersectionObserverEntry :: JSM GType
gTypeIntersectionObserverEntry = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IntersectionObserverEntry"

-- | Functions for this inteface are in "JSDOM.IntersectionObserverEntryInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IntersectionObserverEntryInit Mozilla IntersectionObserverEntryInit documentation>
newtype IntersectionObserverEntryInit = IntersectionObserverEntryInit { IntersectionObserverEntryInit -> JSVal
unIntersectionObserverEntryInit :: JSVal }

instance PToJSVal IntersectionObserverEntryInit where
  pToJSVal :: IntersectionObserverEntryInit -> JSVal
pToJSVal = IntersectionObserverEntryInit -> JSVal
unIntersectionObserverEntryInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal IntersectionObserverEntryInit where
  pFromJSVal :: JSVal -> IntersectionObserverEntryInit
pFromJSVal = JSVal -> IntersectionObserverEntryInit
IntersectionObserverEntryInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal IntersectionObserverEntryInit where
  toJSVal :: IntersectionObserverEntryInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IntersectionObserverEntryInit -> JSVal)
-> IntersectionObserverEntryInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntersectionObserverEntryInit -> JSVal
unIntersectionObserverEntryInit
  {-# INLINE toJSVal #-}

instance FromJSVal IntersectionObserverEntryInit where
  fromJSVal :: JSVal -> JSM (Maybe IntersectionObserverEntryInit)
fromJSVal JSVal
v = (JSVal -> IntersectionObserverEntryInit)
-> Maybe JSVal -> Maybe IntersectionObserverEntryInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IntersectionObserverEntryInit
IntersectionObserverEntryInit (Maybe JSVal -> Maybe IntersectionObserverEntryInit)
-> JSM (Maybe JSVal) -> JSM (Maybe IntersectionObserverEntryInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IntersectionObserverEntryInit
fromJSValUnchecked = IntersectionObserverEntryInit -> JSM IntersectionObserverEntryInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IntersectionObserverEntryInit
 -> JSM IntersectionObserverEntryInit)
-> (JSVal -> IntersectionObserverEntryInit)
-> JSVal
-> JSM IntersectionObserverEntryInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IntersectionObserverEntryInit
IntersectionObserverEntryInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IntersectionObserverEntryInit where
  makeObject :: IntersectionObserverEntryInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IntersectionObserverEntryInit -> JSVal)
-> IntersectionObserverEntryInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntersectionObserverEntryInit -> JSVal
unIntersectionObserverEntryInit

instance IsGObject IntersectionObserverEntryInit where
  typeGType :: IntersectionObserverEntryInit -> JSM GType
typeGType IntersectionObserverEntryInit
_ = JSM GType
gTypeIntersectionObserverEntryInit
  {-# INLINE typeGType #-}

noIntersectionObserverEntryInit :: Maybe IntersectionObserverEntryInit
noIntersectionObserverEntryInit :: Maybe IntersectionObserverEntryInit
noIntersectionObserverEntryInit = Maybe IntersectionObserverEntryInit
forall a. Maybe a
Nothing
{-# INLINE noIntersectionObserverEntryInit #-}

gTypeIntersectionObserverEntryInit :: JSM GType
gTypeIntersectionObserverEntryInit :: JSM GType
gTypeIntersectionObserverEntryInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IntersectionObserverEntryInit"

-- | Functions for this inteface are in "JSDOM.IntersectionObserverInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/IntersectionObserverInit Mozilla IntersectionObserverInit documentation>
newtype IntersectionObserverInit = IntersectionObserverInit { IntersectionObserverInit -> JSVal
unIntersectionObserverInit :: JSVal }

instance PToJSVal IntersectionObserverInit where
  pToJSVal :: IntersectionObserverInit -> JSVal
pToJSVal = IntersectionObserverInit -> JSVal
unIntersectionObserverInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal IntersectionObserverInit where
  pFromJSVal :: JSVal -> IntersectionObserverInit
pFromJSVal = JSVal -> IntersectionObserverInit
IntersectionObserverInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal IntersectionObserverInit where
  toJSVal :: IntersectionObserverInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (IntersectionObserverInit -> JSVal)
-> IntersectionObserverInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntersectionObserverInit -> JSVal
unIntersectionObserverInit
  {-# INLINE toJSVal #-}

instance FromJSVal IntersectionObserverInit where
  fromJSVal :: JSVal -> JSM (Maybe IntersectionObserverInit)
fromJSVal JSVal
v = (JSVal -> IntersectionObserverInit)
-> Maybe JSVal -> Maybe IntersectionObserverInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> IntersectionObserverInit
IntersectionObserverInit (Maybe JSVal -> Maybe IntersectionObserverInit)
-> JSM (Maybe JSVal) -> JSM (Maybe IntersectionObserverInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM IntersectionObserverInit
fromJSValUnchecked = IntersectionObserverInit -> JSM IntersectionObserverInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (IntersectionObserverInit -> JSM IntersectionObserverInit)
-> (JSVal -> IntersectionObserverInit)
-> JSVal
-> JSM IntersectionObserverInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> IntersectionObserverInit
IntersectionObserverInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject IntersectionObserverInit where
  makeObject :: IntersectionObserverInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (IntersectionObserverInit -> JSVal)
-> IntersectionObserverInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntersectionObserverInit -> JSVal
unIntersectionObserverInit

instance IsGObject IntersectionObserverInit where
  typeGType :: IntersectionObserverInit -> JSM GType
typeGType IntersectionObserverInit
_ = JSM GType
gTypeIntersectionObserverInit
  {-# INLINE typeGType #-}

noIntersectionObserverInit :: Maybe IntersectionObserverInit
noIntersectionObserverInit :: Maybe IntersectionObserverInit
noIntersectionObserverInit = Maybe IntersectionObserverInit
forall a. Maybe a
Nothing
{-# INLINE noIntersectionObserverInit #-}

gTypeIntersectionObserverInit :: JSM GType
gTypeIntersectionObserverInit :: JSM GType
gTypeIntersectionObserverInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IntersectionObserverInit"

-- | Functions for this inteface are in "JSDOM.JsonWebKey".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/JsonWebKey Mozilla JsonWebKey documentation>
newtype JsonWebKey = JsonWebKey { JsonWebKey -> JSVal
unJsonWebKey :: JSVal }

instance PToJSVal JsonWebKey where
  pToJSVal :: JsonWebKey -> JSVal
pToJSVal = JsonWebKey -> JSVal
unJsonWebKey
  {-# INLINE pToJSVal #-}

instance PFromJSVal JsonWebKey where
  pFromJSVal :: JSVal -> JsonWebKey
pFromJSVal = JSVal -> JsonWebKey
JsonWebKey
  {-# INLINE pFromJSVal #-}

instance ToJSVal JsonWebKey where
  toJSVal :: JsonWebKey -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (JsonWebKey -> JSVal) -> JsonWebKey -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JsonWebKey -> JSVal
unJsonWebKey
  {-# INLINE toJSVal #-}

instance FromJSVal JsonWebKey where
  fromJSVal :: JSVal -> JSM (Maybe JsonWebKey)
fromJSVal JSVal
v = (JSVal -> JsonWebKey) -> Maybe JSVal -> Maybe JsonWebKey
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> JsonWebKey
JsonWebKey (Maybe JSVal -> Maybe JsonWebKey)
-> JSM (Maybe JSVal) -> JSM (Maybe JsonWebKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM JsonWebKey
fromJSValUnchecked = JsonWebKey -> JSM JsonWebKey
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JsonWebKey -> JSM JsonWebKey)
-> (JSVal -> JsonWebKey) -> JSVal -> JSM JsonWebKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> JsonWebKey
JsonWebKey
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject JsonWebKey where
  makeObject :: JsonWebKey -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (JsonWebKey -> JSVal) -> JsonWebKey -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JsonWebKey -> JSVal
unJsonWebKey

instance IsGObject JsonWebKey where
  typeGType :: JsonWebKey -> JSM GType
typeGType JsonWebKey
_ = JSM GType
gTypeJsonWebKey
  {-# INLINE typeGType #-}

noJsonWebKey :: Maybe JsonWebKey
noJsonWebKey :: Maybe JsonWebKey
noJsonWebKey = Maybe JsonWebKey
forall a. Maybe a
Nothing
{-# INLINE noJsonWebKey #-}

gTypeJsonWebKey :: JSM GType
gTypeJsonWebKey :: JSM GType
gTypeJsonWebKey = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"JsonWebKey"

-- | Functions for this inteface are in "JSDOM.KeyboardEvent".
-- Base interface functions are in:
--
--     * "JSDOM.UIEvent"
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/KeyboardEvent Mozilla KeyboardEvent documentation>
newtype KeyboardEvent = KeyboardEvent { KeyboardEvent -> JSVal
unKeyboardEvent :: JSVal }

instance PToJSVal KeyboardEvent where
  pToJSVal :: KeyboardEvent -> JSVal
pToJSVal = KeyboardEvent -> JSVal
unKeyboardEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal KeyboardEvent where
  pFromJSVal :: JSVal -> KeyboardEvent
pFromJSVal = JSVal -> KeyboardEvent
KeyboardEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal KeyboardEvent where
  toJSVal :: KeyboardEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (KeyboardEvent -> JSVal) -> KeyboardEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyboardEvent -> JSVal
unKeyboardEvent
  {-# INLINE toJSVal #-}

instance FromJSVal KeyboardEvent where
  fromJSVal :: JSVal -> JSM (Maybe KeyboardEvent)
fromJSVal JSVal
v = (JSVal -> KeyboardEvent) -> Maybe JSVal -> Maybe KeyboardEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> KeyboardEvent
KeyboardEvent (Maybe JSVal -> Maybe KeyboardEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe KeyboardEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM KeyboardEvent
fromJSValUnchecked = KeyboardEvent -> JSM KeyboardEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyboardEvent -> JSM KeyboardEvent)
-> (JSVal -> KeyboardEvent) -> JSVal -> JSM KeyboardEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> KeyboardEvent
KeyboardEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject KeyboardEvent where
  makeObject :: KeyboardEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (KeyboardEvent -> JSVal) -> KeyboardEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyboardEvent -> JSVal
unKeyboardEvent

instance IsUIEvent KeyboardEvent
instance IsEvent KeyboardEvent
instance IsGObject KeyboardEvent where
  typeGType :: KeyboardEvent -> JSM GType
typeGType KeyboardEvent
_ = JSM GType
gTypeKeyboardEvent
  {-# INLINE typeGType #-}

noKeyboardEvent :: Maybe KeyboardEvent
noKeyboardEvent :: Maybe KeyboardEvent
noKeyboardEvent = Maybe KeyboardEvent
forall a. Maybe a
Nothing
{-# INLINE noKeyboardEvent #-}

gTypeKeyboardEvent :: JSM GType
gTypeKeyboardEvent :: JSM GType
gTypeKeyboardEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"KeyboardEvent"

-- | Functions for this inteface are in "JSDOM.KeyboardEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventModifierInit"
--     * "JSDOM.UIEventInit"
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/KeyboardEventInit Mozilla KeyboardEventInit documentation>
newtype KeyboardEventInit = KeyboardEventInit { KeyboardEventInit -> JSVal
unKeyboardEventInit :: JSVal }

instance PToJSVal KeyboardEventInit where
  pToJSVal :: KeyboardEventInit -> JSVal
pToJSVal = KeyboardEventInit -> JSVal
unKeyboardEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal KeyboardEventInit where
  pFromJSVal :: JSVal -> KeyboardEventInit
pFromJSVal = JSVal -> KeyboardEventInit
KeyboardEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal KeyboardEventInit where
  toJSVal :: KeyboardEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (KeyboardEventInit -> JSVal) -> KeyboardEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyboardEventInit -> JSVal
unKeyboardEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal KeyboardEventInit where
  fromJSVal :: JSVal -> JSM (Maybe KeyboardEventInit)
fromJSVal JSVal
v = (JSVal -> KeyboardEventInit)
-> Maybe JSVal -> Maybe KeyboardEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> KeyboardEventInit
KeyboardEventInit (Maybe JSVal -> Maybe KeyboardEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe KeyboardEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM KeyboardEventInit
fromJSValUnchecked = KeyboardEventInit -> JSM KeyboardEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyboardEventInit -> JSM KeyboardEventInit)
-> (JSVal -> KeyboardEventInit) -> JSVal -> JSM KeyboardEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> KeyboardEventInit
KeyboardEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject KeyboardEventInit where
  makeObject :: KeyboardEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (KeyboardEventInit -> JSVal) -> KeyboardEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyboardEventInit -> JSVal
unKeyboardEventInit

instance IsEventModifierInit KeyboardEventInit
instance IsUIEventInit KeyboardEventInit
instance IsEventInit KeyboardEventInit
instance IsGObject KeyboardEventInit where
  typeGType :: KeyboardEventInit -> JSM GType
typeGType KeyboardEventInit
_ = JSM GType
gTypeKeyboardEventInit
  {-# INLINE typeGType #-}

noKeyboardEventInit :: Maybe KeyboardEventInit
noKeyboardEventInit :: Maybe KeyboardEventInit
noKeyboardEventInit = Maybe KeyboardEventInit
forall a. Maybe a
Nothing
{-# INLINE noKeyboardEventInit #-}

gTypeKeyboardEventInit :: JSM GType
gTypeKeyboardEventInit :: JSM GType
gTypeKeyboardEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"KeyboardEventInit"

-- | Functions for this inteface are in "JSDOM.KeyframeEffect".
-- Base interface functions are in:
--
--     * "JSDOM.AnimationEffect"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/KeyframeEffect Mozilla KeyframeEffect documentation>
newtype KeyframeEffect = KeyframeEffect { KeyframeEffect -> JSVal
unKeyframeEffect :: JSVal }

instance PToJSVal KeyframeEffect where
  pToJSVal :: KeyframeEffect -> JSVal
pToJSVal = KeyframeEffect -> JSVal
unKeyframeEffect
  {-# INLINE pToJSVal #-}

instance PFromJSVal KeyframeEffect where
  pFromJSVal :: JSVal -> KeyframeEffect
pFromJSVal = JSVal -> KeyframeEffect
KeyframeEffect
  {-# INLINE pFromJSVal #-}

instance ToJSVal KeyframeEffect where
  toJSVal :: KeyframeEffect -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (KeyframeEffect -> JSVal) -> KeyframeEffect -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyframeEffect -> JSVal
unKeyframeEffect
  {-# INLINE toJSVal #-}

instance FromJSVal KeyframeEffect where
  fromJSVal :: JSVal -> JSM (Maybe KeyframeEffect)
fromJSVal JSVal
v = (JSVal -> KeyframeEffect) -> Maybe JSVal -> Maybe KeyframeEffect
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> KeyframeEffect
KeyframeEffect (Maybe JSVal -> Maybe KeyframeEffect)
-> JSM (Maybe JSVal) -> JSM (Maybe KeyframeEffect)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM KeyframeEffect
fromJSValUnchecked = KeyframeEffect -> JSM KeyframeEffect
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyframeEffect -> JSM KeyframeEffect)
-> (JSVal -> KeyframeEffect) -> JSVal -> JSM KeyframeEffect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> KeyframeEffect
KeyframeEffect
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject KeyframeEffect where
  makeObject :: KeyframeEffect -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (KeyframeEffect -> JSVal) -> KeyframeEffect -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyframeEffect -> JSVal
unKeyframeEffect

instance IsAnimationEffect KeyframeEffect
instance IsGObject KeyframeEffect where
  typeGType :: KeyframeEffect -> JSM GType
typeGType KeyframeEffect
_ = JSM GType
gTypeKeyframeEffect
  {-# INLINE typeGType #-}

noKeyframeEffect :: Maybe KeyframeEffect
noKeyframeEffect :: Maybe KeyframeEffect
noKeyframeEffect = Maybe KeyframeEffect
forall a. Maybe a
Nothing
{-# INLINE noKeyframeEffect #-}

gTypeKeyframeEffect :: JSM GType
gTypeKeyframeEffect :: JSM GType
gTypeKeyframeEffect = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"KeyframeEffect"

-- | Functions for this inteface are in "JSDOM.Location".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Location Mozilla Location documentation>
newtype Location = Location { Location -> JSVal
unLocation :: JSVal }

instance PToJSVal Location where
  pToJSVal :: Location -> JSVal
pToJSVal = Location -> JSVal
unLocation
  {-# INLINE pToJSVal #-}

instance PFromJSVal Location where
  pFromJSVal :: JSVal -> Location
pFromJSVal = JSVal -> Location
Location
  {-# INLINE pFromJSVal #-}

instance ToJSVal Location where
  toJSVal :: Location -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Location -> JSVal) -> Location -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Location -> JSVal
unLocation
  {-# INLINE toJSVal #-}

instance FromJSVal Location where
  fromJSVal :: JSVal -> JSM (Maybe Location)
fromJSVal JSVal
v = (JSVal -> Location) -> Maybe JSVal -> Maybe Location
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Location
Location (Maybe JSVal -> Maybe Location)
-> JSM (Maybe JSVal) -> JSM (Maybe Location)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Location
fromJSValUnchecked = Location -> JSM Location
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Location -> JSM Location)
-> (JSVal -> Location) -> JSVal -> JSM Location
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Location
Location
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Location where
  makeObject :: Location -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Location -> JSVal) -> Location -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Location -> JSVal
unLocation

instance IsGObject Location where
  typeGType :: Location -> JSM GType
typeGType Location
_ = JSM GType
gTypeLocation
  {-# INLINE typeGType #-}

noLocation :: Maybe Location
noLocation :: Maybe Location
noLocation = Maybe Location
forall a. Maybe a
Nothing
{-# INLINE noLocation #-}

gTypeLocation :: JSM GType
gTypeLocation :: JSM GType
gTypeLocation = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Location"

-- | Functions for this inteface are in "JSDOM.LongRange".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/LongRange Mozilla LongRange documentation>
newtype LongRange = LongRange { LongRange -> JSVal
unLongRange :: JSVal }

instance PToJSVal LongRange where
  pToJSVal :: LongRange -> JSVal
pToJSVal = LongRange -> JSVal
unLongRange
  {-# INLINE pToJSVal #-}

instance PFromJSVal LongRange where
  pFromJSVal :: JSVal -> LongRange
pFromJSVal = JSVal -> LongRange
LongRange
  {-# INLINE pFromJSVal #-}

instance ToJSVal LongRange where
  toJSVal :: LongRange -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (LongRange -> JSVal) -> LongRange -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LongRange -> JSVal
unLongRange
  {-# INLINE toJSVal #-}

instance FromJSVal LongRange where
  fromJSVal :: JSVal -> JSM (Maybe LongRange)
fromJSVal JSVal
v = (JSVal -> LongRange) -> Maybe JSVal -> Maybe LongRange
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> LongRange
LongRange (Maybe JSVal -> Maybe LongRange)
-> JSM (Maybe JSVal) -> JSM (Maybe LongRange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM LongRange
fromJSValUnchecked = LongRange -> JSM LongRange
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (LongRange -> JSM LongRange)
-> (JSVal -> LongRange) -> JSVal -> JSM LongRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> LongRange
LongRange
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject LongRange where
  makeObject :: LongRange -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (LongRange -> JSVal) -> LongRange -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LongRange -> JSVal
unLongRange

class (IsGObject o) => IsLongRange o
toLongRange :: IsLongRange o => o -> LongRange
toLongRange :: forall o. IsLongRange o => o -> LongRange
toLongRange = JSVal -> LongRange
LongRange (JSVal -> LongRange) -> (o -> JSVal) -> o -> LongRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsLongRange LongRange
instance IsGObject LongRange where
  typeGType :: LongRange -> JSM GType
typeGType LongRange
_ = JSM GType
gTypeLongRange
  {-# INLINE typeGType #-}

noLongRange :: Maybe LongRange
noLongRange :: Maybe LongRange
noLongRange = Maybe LongRange
forall a. Maybe a
Nothing
{-# INLINE noLongRange #-}

gTypeLongRange :: JSM GType
gTypeLongRange :: JSM GType
gTypeLongRange = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"LongRange"

-- | Functions for this inteface are in "JSDOM.MediaController".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaController Mozilla MediaController documentation>
newtype MediaController = MediaController { MediaController -> JSVal
unMediaController :: JSVal }

instance PToJSVal MediaController where
  pToJSVal :: MediaController -> JSVal
pToJSVal = MediaController -> JSVal
unMediaController
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaController where
  pFromJSVal :: JSVal -> MediaController
pFromJSVal = JSVal -> MediaController
MediaController
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaController where
  toJSVal :: MediaController -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaController -> JSVal) -> MediaController -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaController -> JSVal
unMediaController
  {-# INLINE toJSVal #-}

instance FromJSVal MediaController where
  fromJSVal :: JSVal -> JSM (Maybe MediaController)
fromJSVal JSVal
v = (JSVal -> MediaController) -> Maybe JSVal -> Maybe MediaController
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaController
MediaController (Maybe JSVal -> Maybe MediaController)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaController)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaController
fromJSValUnchecked = MediaController -> JSM MediaController
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaController -> JSM MediaController)
-> (JSVal -> MediaController) -> JSVal -> JSM MediaController
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaController
MediaController
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaController where
  makeObject :: MediaController -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaController -> JSVal) -> MediaController -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaController -> JSVal
unMediaController

instance IsEventTarget MediaController
instance IsGObject MediaController where
  typeGType :: MediaController -> JSM GType
typeGType MediaController
_ = JSM GType
gTypeMediaController
  {-# INLINE typeGType #-}

noMediaController :: Maybe MediaController
noMediaController :: Maybe MediaController
noMediaController = Maybe MediaController
forall a. Maybe a
Nothing
{-# INLINE noMediaController #-}

gTypeMediaController :: JSM GType
gTypeMediaController :: JSM GType
gTypeMediaController = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaController"

-- | Functions for this inteface are in "JSDOM.MediaControlsHost".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaControlsHost Mozilla MediaControlsHost documentation>
newtype MediaControlsHost = MediaControlsHost { MediaControlsHost -> JSVal
unMediaControlsHost :: JSVal }

instance PToJSVal MediaControlsHost where
  pToJSVal :: MediaControlsHost -> JSVal
pToJSVal = MediaControlsHost -> JSVal
unMediaControlsHost
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaControlsHost where
  pFromJSVal :: JSVal -> MediaControlsHost
pFromJSVal = JSVal -> MediaControlsHost
MediaControlsHost
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaControlsHost where
  toJSVal :: MediaControlsHost -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaControlsHost -> JSVal) -> MediaControlsHost -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaControlsHost -> JSVal
unMediaControlsHost
  {-# INLINE toJSVal #-}

instance FromJSVal MediaControlsHost where
  fromJSVal :: JSVal -> JSM (Maybe MediaControlsHost)
fromJSVal JSVal
v = (JSVal -> MediaControlsHost)
-> Maybe JSVal -> Maybe MediaControlsHost
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaControlsHost
MediaControlsHost (Maybe JSVal -> Maybe MediaControlsHost)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaControlsHost)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaControlsHost
fromJSValUnchecked = MediaControlsHost -> JSM MediaControlsHost
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaControlsHost -> JSM MediaControlsHost)
-> (JSVal -> MediaControlsHost) -> JSVal -> JSM MediaControlsHost
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaControlsHost
MediaControlsHost
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaControlsHost where
  makeObject :: MediaControlsHost -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaControlsHost -> JSVal) -> MediaControlsHost -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaControlsHost -> JSVal
unMediaControlsHost

instance IsGObject MediaControlsHost where
  typeGType :: MediaControlsHost -> JSM GType
typeGType MediaControlsHost
_ = JSM GType
gTypeMediaControlsHost
  {-# INLINE typeGType #-}

noMediaControlsHost :: Maybe MediaControlsHost
noMediaControlsHost :: Maybe MediaControlsHost
noMediaControlsHost = Maybe MediaControlsHost
forall a. Maybe a
Nothing
{-# INLINE noMediaControlsHost #-}

gTypeMediaControlsHost :: JSM GType
gTypeMediaControlsHost :: JSM GType
gTypeMediaControlsHost = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaControlsHost"

-- | Functions for this inteface are in "JSDOM.MediaDeviceInfo".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaDeviceInfo Mozilla MediaDeviceInfo documentation>
newtype MediaDeviceInfo = MediaDeviceInfo { MediaDeviceInfo -> JSVal
unMediaDeviceInfo :: JSVal }

instance PToJSVal MediaDeviceInfo where
  pToJSVal :: MediaDeviceInfo -> JSVal
pToJSVal = MediaDeviceInfo -> JSVal
unMediaDeviceInfo
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaDeviceInfo where
  pFromJSVal :: JSVal -> MediaDeviceInfo
pFromJSVal = JSVal -> MediaDeviceInfo
MediaDeviceInfo
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaDeviceInfo where
  toJSVal :: MediaDeviceInfo -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaDeviceInfo -> JSVal) -> MediaDeviceInfo -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaDeviceInfo -> JSVal
unMediaDeviceInfo
  {-# INLINE toJSVal #-}

instance FromJSVal MediaDeviceInfo where
  fromJSVal :: JSVal -> JSM (Maybe MediaDeviceInfo)
fromJSVal JSVal
v = (JSVal -> MediaDeviceInfo) -> Maybe JSVal -> Maybe MediaDeviceInfo
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaDeviceInfo
MediaDeviceInfo (Maybe JSVal -> Maybe MediaDeviceInfo)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaDeviceInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaDeviceInfo
fromJSValUnchecked = MediaDeviceInfo -> JSM MediaDeviceInfo
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaDeviceInfo -> JSM MediaDeviceInfo)
-> (JSVal -> MediaDeviceInfo) -> JSVal -> JSM MediaDeviceInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaDeviceInfo
MediaDeviceInfo
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaDeviceInfo where
  makeObject :: MediaDeviceInfo -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaDeviceInfo -> JSVal) -> MediaDeviceInfo -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaDeviceInfo -> JSVal
unMediaDeviceInfo

instance IsGObject MediaDeviceInfo where
  typeGType :: MediaDeviceInfo -> JSM GType
typeGType MediaDeviceInfo
_ = JSM GType
gTypeMediaDeviceInfo
  {-# INLINE typeGType #-}

noMediaDeviceInfo :: Maybe MediaDeviceInfo
noMediaDeviceInfo :: Maybe MediaDeviceInfo
noMediaDeviceInfo = Maybe MediaDeviceInfo
forall a. Maybe a
Nothing
{-# INLINE noMediaDeviceInfo #-}

gTypeMediaDeviceInfo :: JSM GType
gTypeMediaDeviceInfo :: JSM GType
gTypeMediaDeviceInfo = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaDeviceInfo"

-- | Functions for this inteface are in "JSDOM.MediaDevices".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaDevices Mozilla MediaDevices documentation>
newtype MediaDevices = MediaDevices { MediaDevices -> JSVal
unMediaDevices :: JSVal }

instance PToJSVal MediaDevices where
  pToJSVal :: MediaDevices -> JSVal
pToJSVal = MediaDevices -> JSVal
unMediaDevices
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaDevices where
  pFromJSVal :: JSVal -> MediaDevices
pFromJSVal = JSVal -> MediaDevices
MediaDevices
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaDevices where
  toJSVal :: MediaDevices -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaDevices -> JSVal) -> MediaDevices -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaDevices -> JSVal
unMediaDevices
  {-# INLINE toJSVal #-}

instance FromJSVal MediaDevices where
  fromJSVal :: JSVal -> JSM (Maybe MediaDevices)
fromJSVal JSVal
v = (JSVal -> MediaDevices) -> Maybe JSVal -> Maybe MediaDevices
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaDevices
MediaDevices (Maybe JSVal -> Maybe MediaDevices)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaDevices)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaDevices
fromJSValUnchecked = MediaDevices -> JSM MediaDevices
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaDevices -> JSM MediaDevices)
-> (JSVal -> MediaDevices) -> JSVal -> JSM MediaDevices
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaDevices
MediaDevices
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaDevices where
  makeObject :: MediaDevices -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaDevices -> JSVal) -> MediaDevices -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaDevices -> JSVal
unMediaDevices

instance IsGObject MediaDevices where
  typeGType :: MediaDevices -> JSM GType
typeGType MediaDevices
_ = JSM GType
gTypeMediaDevices
  {-# INLINE typeGType #-}

noMediaDevices :: Maybe MediaDevices
noMediaDevices :: Maybe MediaDevices
noMediaDevices = Maybe MediaDevices
forall a. Maybe a
Nothing
{-# INLINE noMediaDevices #-}

gTypeMediaDevices :: JSM GType
gTypeMediaDevices :: JSM GType
gTypeMediaDevices = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaDevices"

-- | Functions for this inteface are in "JSDOM.MediaElementAudioSourceNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaElementAudioSourceNode Mozilla MediaElementAudioSourceNode documentation>
newtype MediaElementAudioSourceNode = MediaElementAudioSourceNode { MediaElementAudioSourceNode -> JSVal
unMediaElementAudioSourceNode :: JSVal }

instance PToJSVal MediaElementAudioSourceNode where
  pToJSVal :: MediaElementAudioSourceNode -> JSVal
pToJSVal = MediaElementAudioSourceNode -> JSVal
unMediaElementAudioSourceNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaElementAudioSourceNode where
  pFromJSVal :: JSVal -> MediaElementAudioSourceNode
pFromJSVal = JSVal -> MediaElementAudioSourceNode
MediaElementAudioSourceNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaElementAudioSourceNode where
  toJSVal :: MediaElementAudioSourceNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaElementAudioSourceNode -> JSVal)
-> MediaElementAudioSourceNode
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaElementAudioSourceNode -> JSVal
unMediaElementAudioSourceNode
  {-# INLINE toJSVal #-}

instance FromJSVal MediaElementAudioSourceNode where
  fromJSVal :: JSVal -> JSM (Maybe MediaElementAudioSourceNode)
fromJSVal JSVal
v = (JSVal -> MediaElementAudioSourceNode)
-> Maybe JSVal -> Maybe MediaElementAudioSourceNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaElementAudioSourceNode
MediaElementAudioSourceNode (Maybe JSVal -> Maybe MediaElementAudioSourceNode)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaElementAudioSourceNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaElementAudioSourceNode
fromJSValUnchecked = MediaElementAudioSourceNode -> JSM MediaElementAudioSourceNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaElementAudioSourceNode -> JSM MediaElementAudioSourceNode)
-> (JSVal -> MediaElementAudioSourceNode)
-> JSVal
-> JSM MediaElementAudioSourceNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaElementAudioSourceNode
MediaElementAudioSourceNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaElementAudioSourceNode where
  makeObject :: MediaElementAudioSourceNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaElementAudioSourceNode -> JSVal)
-> MediaElementAudioSourceNode
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaElementAudioSourceNode -> JSVal
unMediaElementAudioSourceNode

instance IsAudioNode MediaElementAudioSourceNode
instance IsEventTarget MediaElementAudioSourceNode
instance IsGObject MediaElementAudioSourceNode where
  typeGType :: MediaElementAudioSourceNode -> JSM GType
typeGType MediaElementAudioSourceNode
_ = JSM GType
gTypeMediaElementAudioSourceNode
  {-# INLINE typeGType #-}

noMediaElementAudioSourceNode :: Maybe MediaElementAudioSourceNode
noMediaElementAudioSourceNode :: Maybe MediaElementAudioSourceNode
noMediaElementAudioSourceNode = Maybe MediaElementAudioSourceNode
forall a. Maybe a
Nothing
{-# INLINE noMediaElementAudioSourceNode #-}

gTypeMediaElementAudioSourceNode :: JSM GType
gTypeMediaElementAudioSourceNode :: JSM GType
gTypeMediaElementAudioSourceNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaElementAudioSourceNode"

-- | Functions for this inteface are in "JSDOM.MediaEncryptedEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaEncryptedEvent Mozilla MediaEncryptedEvent documentation>
newtype MediaEncryptedEvent = MediaEncryptedEvent { MediaEncryptedEvent -> JSVal
unMediaEncryptedEvent :: JSVal }

instance PToJSVal MediaEncryptedEvent where
  pToJSVal :: MediaEncryptedEvent -> JSVal
pToJSVal = MediaEncryptedEvent -> JSVal
unMediaEncryptedEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaEncryptedEvent where
  pFromJSVal :: JSVal -> MediaEncryptedEvent
pFromJSVal = JSVal -> MediaEncryptedEvent
MediaEncryptedEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaEncryptedEvent where
  toJSVal :: MediaEncryptedEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaEncryptedEvent -> JSVal)
-> MediaEncryptedEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaEncryptedEvent -> JSVal
unMediaEncryptedEvent
  {-# INLINE toJSVal #-}

instance FromJSVal MediaEncryptedEvent where
  fromJSVal :: JSVal -> JSM (Maybe MediaEncryptedEvent)
fromJSVal JSVal
v = (JSVal -> MediaEncryptedEvent)
-> Maybe JSVal -> Maybe MediaEncryptedEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaEncryptedEvent
MediaEncryptedEvent (Maybe JSVal -> Maybe MediaEncryptedEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaEncryptedEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaEncryptedEvent
fromJSValUnchecked = MediaEncryptedEvent -> JSM MediaEncryptedEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaEncryptedEvent -> JSM MediaEncryptedEvent)
-> (JSVal -> MediaEncryptedEvent)
-> JSVal
-> JSM MediaEncryptedEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaEncryptedEvent
MediaEncryptedEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaEncryptedEvent where
  makeObject :: MediaEncryptedEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaEncryptedEvent -> JSVal)
-> MediaEncryptedEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaEncryptedEvent -> JSVal
unMediaEncryptedEvent

instance IsEvent MediaEncryptedEvent
instance IsGObject MediaEncryptedEvent where
  typeGType :: MediaEncryptedEvent -> JSM GType
typeGType MediaEncryptedEvent
_ = JSM GType
gTypeMediaEncryptedEvent
  {-# INLINE typeGType #-}

noMediaEncryptedEvent :: Maybe MediaEncryptedEvent
noMediaEncryptedEvent :: Maybe MediaEncryptedEvent
noMediaEncryptedEvent = Maybe MediaEncryptedEvent
forall a. Maybe a
Nothing
{-# INLINE noMediaEncryptedEvent #-}

gTypeMediaEncryptedEvent :: JSM GType
gTypeMediaEncryptedEvent :: JSM GType
gTypeMediaEncryptedEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaEncryptedEvent"

-- | Functions for this inteface are in "JSDOM.MediaEncryptedEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaEncryptedEventInit Mozilla MediaEncryptedEventInit documentation>
newtype MediaEncryptedEventInit = MediaEncryptedEventInit { MediaEncryptedEventInit -> JSVal
unMediaEncryptedEventInit :: JSVal }

instance PToJSVal MediaEncryptedEventInit where
  pToJSVal :: MediaEncryptedEventInit -> JSVal
pToJSVal = MediaEncryptedEventInit -> JSVal
unMediaEncryptedEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaEncryptedEventInit where
  pFromJSVal :: JSVal -> MediaEncryptedEventInit
pFromJSVal = JSVal -> MediaEncryptedEventInit
MediaEncryptedEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaEncryptedEventInit where
  toJSVal :: MediaEncryptedEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaEncryptedEventInit -> JSVal)
-> MediaEncryptedEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaEncryptedEventInit -> JSVal
unMediaEncryptedEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal MediaEncryptedEventInit where
  fromJSVal :: JSVal -> JSM (Maybe MediaEncryptedEventInit)
fromJSVal JSVal
v = (JSVal -> MediaEncryptedEventInit)
-> Maybe JSVal -> Maybe MediaEncryptedEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaEncryptedEventInit
MediaEncryptedEventInit (Maybe JSVal -> Maybe MediaEncryptedEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaEncryptedEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaEncryptedEventInit
fromJSValUnchecked = MediaEncryptedEventInit -> JSM MediaEncryptedEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaEncryptedEventInit -> JSM MediaEncryptedEventInit)
-> (JSVal -> MediaEncryptedEventInit)
-> JSVal
-> JSM MediaEncryptedEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaEncryptedEventInit
MediaEncryptedEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaEncryptedEventInit where
  makeObject :: MediaEncryptedEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaEncryptedEventInit -> JSVal)
-> MediaEncryptedEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaEncryptedEventInit -> JSVal
unMediaEncryptedEventInit

instance IsEventInit MediaEncryptedEventInit
instance IsGObject MediaEncryptedEventInit where
  typeGType :: MediaEncryptedEventInit -> JSM GType
typeGType MediaEncryptedEventInit
_ = JSM GType
gTypeMediaEncryptedEventInit
  {-# INLINE typeGType #-}

noMediaEncryptedEventInit :: Maybe MediaEncryptedEventInit
noMediaEncryptedEventInit :: Maybe MediaEncryptedEventInit
noMediaEncryptedEventInit = Maybe MediaEncryptedEventInit
forall a. Maybe a
Nothing
{-# INLINE noMediaEncryptedEventInit #-}

gTypeMediaEncryptedEventInit :: JSM GType
gTypeMediaEncryptedEventInit :: JSM GType
gTypeMediaEncryptedEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaEncryptedEventInit"

-- | Functions for this inteface are in "JSDOM.MediaError".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaError Mozilla MediaError documentation>
newtype MediaError = MediaError { MediaError -> JSVal
unMediaError :: JSVal }

instance PToJSVal MediaError where
  pToJSVal :: MediaError -> JSVal
pToJSVal = MediaError -> JSVal
unMediaError
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaError where
  pFromJSVal :: JSVal -> MediaError
pFromJSVal = JSVal -> MediaError
MediaError
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaError where
  toJSVal :: MediaError -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaError -> JSVal) -> MediaError -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaError -> JSVal
unMediaError
  {-# INLINE toJSVal #-}

instance FromJSVal MediaError where
  fromJSVal :: JSVal -> JSM (Maybe MediaError)
fromJSVal JSVal
v = (JSVal -> MediaError) -> Maybe JSVal -> Maybe MediaError
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaError
MediaError (Maybe JSVal -> Maybe MediaError)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaError
fromJSValUnchecked = MediaError -> JSM MediaError
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaError -> JSM MediaError)
-> (JSVal -> MediaError) -> JSVal -> JSM MediaError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaError
MediaError
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaError where
  makeObject :: MediaError -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaError -> JSVal) -> MediaError -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaError -> JSVal
unMediaError

instance IsGObject MediaError where
  typeGType :: MediaError -> JSM GType
typeGType MediaError
_ = JSM GType
gTypeMediaError
  {-# INLINE typeGType #-}

noMediaError :: Maybe MediaError
noMediaError :: Maybe MediaError
noMediaError = Maybe MediaError
forall a. Maybe a
Nothing
{-# INLINE noMediaError #-}

gTypeMediaError :: JSM GType
gTypeMediaError :: JSM GType
gTypeMediaError = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaError"

-- | Functions for this inteface are in "JSDOM.MediaKeyMessageEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitMediaKeyMessageEvent Mozilla WebKitMediaKeyMessageEvent documentation>
newtype MediaKeyMessageEvent = MediaKeyMessageEvent { MediaKeyMessageEvent -> JSVal
unMediaKeyMessageEvent :: JSVal }

instance PToJSVal MediaKeyMessageEvent where
  pToJSVal :: MediaKeyMessageEvent -> JSVal
pToJSVal = MediaKeyMessageEvent -> JSVal
unMediaKeyMessageEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaKeyMessageEvent where
  pFromJSVal :: JSVal -> MediaKeyMessageEvent
pFromJSVal = JSVal -> MediaKeyMessageEvent
MediaKeyMessageEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaKeyMessageEvent where
  toJSVal :: MediaKeyMessageEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaKeyMessageEvent -> JSVal)
-> MediaKeyMessageEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeyMessageEvent -> JSVal
unMediaKeyMessageEvent
  {-# INLINE toJSVal #-}

instance FromJSVal MediaKeyMessageEvent where
  fromJSVal :: JSVal -> JSM (Maybe MediaKeyMessageEvent)
fromJSVal JSVal
v = (JSVal -> MediaKeyMessageEvent)
-> Maybe JSVal -> Maybe MediaKeyMessageEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaKeyMessageEvent
MediaKeyMessageEvent (Maybe JSVal -> Maybe MediaKeyMessageEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaKeyMessageEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaKeyMessageEvent
fromJSValUnchecked = MediaKeyMessageEvent -> JSM MediaKeyMessageEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeyMessageEvent -> JSM MediaKeyMessageEvent)
-> (JSVal -> MediaKeyMessageEvent)
-> JSVal
-> JSM MediaKeyMessageEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaKeyMessageEvent
MediaKeyMessageEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaKeyMessageEvent where
  makeObject :: MediaKeyMessageEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaKeyMessageEvent -> JSVal)
-> MediaKeyMessageEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeyMessageEvent -> JSVal
unMediaKeyMessageEvent

instance IsEvent MediaKeyMessageEvent
instance IsGObject MediaKeyMessageEvent where
  typeGType :: MediaKeyMessageEvent -> JSM GType
typeGType MediaKeyMessageEvent
_ = JSM GType
gTypeMediaKeyMessageEvent
  {-# INLINE typeGType #-}

noMediaKeyMessageEvent :: Maybe MediaKeyMessageEvent
noMediaKeyMessageEvent :: Maybe MediaKeyMessageEvent
noMediaKeyMessageEvent = Maybe MediaKeyMessageEvent
forall a. Maybe a
Nothing
{-# INLINE noMediaKeyMessageEvent #-}

gTypeMediaKeyMessageEvent :: JSM GType
gTypeMediaKeyMessageEvent :: JSM GType
gTypeMediaKeyMessageEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitMediaKeyMessageEvent"

-- | Functions for this inteface are in "JSDOM.MediaKeyMessageEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaKeyMessageEventInit Mozilla MediaKeyMessageEventInit documentation>
newtype MediaKeyMessageEventInit = MediaKeyMessageEventInit { MediaKeyMessageEventInit -> JSVal
unMediaKeyMessageEventInit :: JSVal }

instance PToJSVal MediaKeyMessageEventInit where
  pToJSVal :: MediaKeyMessageEventInit -> JSVal
pToJSVal = MediaKeyMessageEventInit -> JSVal
unMediaKeyMessageEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaKeyMessageEventInit where
  pFromJSVal :: JSVal -> MediaKeyMessageEventInit
pFromJSVal = JSVal -> MediaKeyMessageEventInit
MediaKeyMessageEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaKeyMessageEventInit where
  toJSVal :: MediaKeyMessageEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaKeyMessageEventInit -> JSVal)
-> MediaKeyMessageEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeyMessageEventInit -> JSVal
unMediaKeyMessageEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal MediaKeyMessageEventInit where
  fromJSVal :: JSVal -> JSM (Maybe MediaKeyMessageEventInit)
fromJSVal JSVal
v = (JSVal -> MediaKeyMessageEventInit)
-> Maybe JSVal -> Maybe MediaKeyMessageEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaKeyMessageEventInit
MediaKeyMessageEventInit (Maybe JSVal -> Maybe MediaKeyMessageEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaKeyMessageEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaKeyMessageEventInit
fromJSValUnchecked = MediaKeyMessageEventInit -> JSM MediaKeyMessageEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeyMessageEventInit -> JSM MediaKeyMessageEventInit)
-> (JSVal -> MediaKeyMessageEventInit)
-> JSVal
-> JSM MediaKeyMessageEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaKeyMessageEventInit
MediaKeyMessageEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaKeyMessageEventInit where
  makeObject :: MediaKeyMessageEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaKeyMessageEventInit -> JSVal)
-> MediaKeyMessageEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeyMessageEventInit -> JSVal
unMediaKeyMessageEventInit

instance IsEventInit MediaKeyMessageEventInit
instance IsGObject MediaKeyMessageEventInit where
  typeGType :: MediaKeyMessageEventInit -> JSM GType
typeGType MediaKeyMessageEventInit
_ = JSM GType
gTypeMediaKeyMessageEventInit
  {-# INLINE typeGType #-}

noMediaKeyMessageEventInit :: Maybe MediaKeyMessageEventInit
noMediaKeyMessageEventInit :: Maybe MediaKeyMessageEventInit
noMediaKeyMessageEventInit = Maybe MediaKeyMessageEventInit
forall a. Maybe a
Nothing
{-# INLINE noMediaKeyMessageEventInit #-}

gTypeMediaKeyMessageEventInit :: JSM GType
gTypeMediaKeyMessageEventInit :: JSM GType
gTypeMediaKeyMessageEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaKeyMessageEventInit"

-- | Functions for this inteface are in "JSDOM.MediaKeySession".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitMediaKeySession Mozilla WebKitMediaKeySession documentation>
newtype MediaKeySession = MediaKeySession { MediaKeySession -> JSVal
unMediaKeySession :: JSVal }

instance PToJSVal MediaKeySession where
  pToJSVal :: MediaKeySession -> JSVal
pToJSVal = MediaKeySession -> JSVal
unMediaKeySession
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaKeySession where
  pFromJSVal :: JSVal -> MediaKeySession
pFromJSVal = JSVal -> MediaKeySession
MediaKeySession
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaKeySession where
  toJSVal :: MediaKeySession -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaKeySession -> JSVal) -> MediaKeySession -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeySession -> JSVal
unMediaKeySession
  {-# INLINE toJSVal #-}

instance FromJSVal MediaKeySession where
  fromJSVal :: JSVal -> JSM (Maybe MediaKeySession)
fromJSVal JSVal
v = (JSVal -> MediaKeySession) -> Maybe JSVal -> Maybe MediaKeySession
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaKeySession
MediaKeySession (Maybe JSVal -> Maybe MediaKeySession)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaKeySession)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaKeySession
fromJSValUnchecked = MediaKeySession -> JSM MediaKeySession
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeySession -> JSM MediaKeySession)
-> (JSVal -> MediaKeySession) -> JSVal -> JSM MediaKeySession
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaKeySession
MediaKeySession
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaKeySession where
  makeObject :: MediaKeySession -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaKeySession -> JSVal) -> MediaKeySession -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeySession -> JSVal
unMediaKeySession

instance IsEventTarget MediaKeySession
instance IsGObject MediaKeySession where
  typeGType :: MediaKeySession -> JSM GType
typeGType MediaKeySession
_ = JSM GType
gTypeMediaKeySession
  {-# INLINE typeGType #-}

noMediaKeySession :: Maybe MediaKeySession
noMediaKeySession :: Maybe MediaKeySession
noMediaKeySession = Maybe MediaKeySession
forall a. Maybe a
Nothing
{-# INLINE noMediaKeySession #-}

gTypeMediaKeySession :: JSM GType
gTypeMediaKeySession :: JSM GType
gTypeMediaKeySession = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitMediaKeySession"

-- | Functions for this inteface are in "JSDOM.MediaKeyStatusMap".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaKeyStatusMap Mozilla MediaKeyStatusMap documentation>
newtype MediaKeyStatusMap = MediaKeyStatusMap { MediaKeyStatusMap -> JSVal
unMediaKeyStatusMap :: JSVal }

instance PToJSVal MediaKeyStatusMap where
  pToJSVal :: MediaKeyStatusMap -> JSVal
pToJSVal = MediaKeyStatusMap -> JSVal
unMediaKeyStatusMap
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaKeyStatusMap where
  pFromJSVal :: JSVal -> MediaKeyStatusMap
pFromJSVal = JSVal -> MediaKeyStatusMap
MediaKeyStatusMap
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaKeyStatusMap where
  toJSVal :: MediaKeyStatusMap -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaKeyStatusMap -> JSVal) -> MediaKeyStatusMap -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeyStatusMap -> JSVal
unMediaKeyStatusMap
  {-# INLINE toJSVal #-}

instance FromJSVal MediaKeyStatusMap where
  fromJSVal :: JSVal -> JSM (Maybe MediaKeyStatusMap)
fromJSVal JSVal
v = (JSVal -> MediaKeyStatusMap)
-> Maybe JSVal -> Maybe MediaKeyStatusMap
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaKeyStatusMap
MediaKeyStatusMap (Maybe JSVal -> Maybe MediaKeyStatusMap)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaKeyStatusMap)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaKeyStatusMap
fromJSValUnchecked = MediaKeyStatusMap -> JSM MediaKeyStatusMap
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeyStatusMap -> JSM MediaKeyStatusMap)
-> (JSVal -> MediaKeyStatusMap) -> JSVal -> JSM MediaKeyStatusMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaKeyStatusMap
MediaKeyStatusMap
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaKeyStatusMap where
  makeObject :: MediaKeyStatusMap -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaKeyStatusMap -> JSVal) -> MediaKeyStatusMap -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeyStatusMap -> JSVal
unMediaKeyStatusMap

instance IsGObject MediaKeyStatusMap where
  typeGType :: MediaKeyStatusMap -> JSM GType
typeGType MediaKeyStatusMap
_ = JSM GType
gTypeMediaKeyStatusMap
  {-# INLINE typeGType #-}

noMediaKeyStatusMap :: Maybe MediaKeyStatusMap
noMediaKeyStatusMap :: Maybe MediaKeyStatusMap
noMediaKeyStatusMap = Maybe MediaKeyStatusMap
forall a. Maybe a
Nothing
{-# INLINE noMediaKeyStatusMap #-}

gTypeMediaKeyStatusMap :: JSM GType
gTypeMediaKeyStatusMap :: JSM GType
gTypeMediaKeyStatusMap = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaKeyStatusMap"

-- | Functions for this inteface are in "JSDOM.MediaKeySystemAccess".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaKeySystemAccess Mozilla MediaKeySystemAccess documentation>
newtype MediaKeySystemAccess = MediaKeySystemAccess { MediaKeySystemAccess -> JSVal
unMediaKeySystemAccess :: JSVal }

instance PToJSVal MediaKeySystemAccess where
  pToJSVal :: MediaKeySystemAccess -> JSVal
pToJSVal = MediaKeySystemAccess -> JSVal
unMediaKeySystemAccess
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaKeySystemAccess where
  pFromJSVal :: JSVal -> MediaKeySystemAccess
pFromJSVal = JSVal -> MediaKeySystemAccess
MediaKeySystemAccess
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaKeySystemAccess where
  toJSVal :: MediaKeySystemAccess -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaKeySystemAccess -> JSVal)
-> MediaKeySystemAccess
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeySystemAccess -> JSVal
unMediaKeySystemAccess
  {-# INLINE toJSVal #-}

instance FromJSVal MediaKeySystemAccess where
  fromJSVal :: JSVal -> JSM (Maybe MediaKeySystemAccess)
fromJSVal JSVal
v = (JSVal -> MediaKeySystemAccess)
-> Maybe JSVal -> Maybe MediaKeySystemAccess
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaKeySystemAccess
MediaKeySystemAccess (Maybe JSVal -> Maybe MediaKeySystemAccess)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaKeySystemAccess)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaKeySystemAccess
fromJSValUnchecked = MediaKeySystemAccess -> JSM MediaKeySystemAccess
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeySystemAccess -> JSM MediaKeySystemAccess)
-> (JSVal -> MediaKeySystemAccess)
-> JSVal
-> JSM MediaKeySystemAccess
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaKeySystemAccess
MediaKeySystemAccess
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaKeySystemAccess where
  makeObject :: MediaKeySystemAccess -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaKeySystemAccess -> JSVal)
-> MediaKeySystemAccess
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeySystemAccess -> JSVal
unMediaKeySystemAccess

instance IsGObject MediaKeySystemAccess where
  typeGType :: MediaKeySystemAccess -> JSM GType
typeGType MediaKeySystemAccess
_ = JSM GType
gTypeMediaKeySystemAccess
  {-# INLINE typeGType #-}

noMediaKeySystemAccess :: Maybe MediaKeySystemAccess
noMediaKeySystemAccess :: Maybe MediaKeySystemAccess
noMediaKeySystemAccess = Maybe MediaKeySystemAccess
forall a. Maybe a
Nothing
{-# INLINE noMediaKeySystemAccess #-}

gTypeMediaKeySystemAccess :: JSM GType
gTypeMediaKeySystemAccess :: JSM GType
gTypeMediaKeySystemAccess = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaKeySystemAccess"

-- | Functions for this inteface are in "JSDOM.MediaKeySystemConfiguration".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaKeySystemConfiguration Mozilla MediaKeySystemConfiguration documentation>
newtype MediaKeySystemConfiguration = MediaKeySystemConfiguration { MediaKeySystemConfiguration -> JSVal
unMediaKeySystemConfiguration :: JSVal }

instance PToJSVal MediaKeySystemConfiguration where
  pToJSVal :: MediaKeySystemConfiguration -> JSVal
pToJSVal = MediaKeySystemConfiguration -> JSVal
unMediaKeySystemConfiguration
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaKeySystemConfiguration where
  pFromJSVal :: JSVal -> MediaKeySystemConfiguration
pFromJSVal = JSVal -> MediaKeySystemConfiguration
MediaKeySystemConfiguration
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaKeySystemConfiguration where
  toJSVal :: MediaKeySystemConfiguration -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaKeySystemConfiguration -> JSVal)
-> MediaKeySystemConfiguration
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeySystemConfiguration -> JSVal
unMediaKeySystemConfiguration
  {-# INLINE toJSVal #-}

instance FromJSVal MediaKeySystemConfiguration where
  fromJSVal :: JSVal -> JSM (Maybe MediaKeySystemConfiguration)
fromJSVal JSVal
v = (JSVal -> MediaKeySystemConfiguration)
-> Maybe JSVal -> Maybe MediaKeySystemConfiguration
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaKeySystemConfiguration
MediaKeySystemConfiguration (Maybe JSVal -> Maybe MediaKeySystemConfiguration)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaKeySystemConfiguration)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaKeySystemConfiguration
fromJSValUnchecked = MediaKeySystemConfiguration -> JSM MediaKeySystemConfiguration
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeySystemConfiguration -> JSM MediaKeySystemConfiguration)
-> (JSVal -> MediaKeySystemConfiguration)
-> JSVal
-> JSM MediaKeySystemConfiguration
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaKeySystemConfiguration
MediaKeySystemConfiguration
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaKeySystemConfiguration where
  makeObject :: MediaKeySystemConfiguration -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaKeySystemConfiguration -> JSVal)
-> MediaKeySystemConfiguration
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeySystemConfiguration -> JSVal
unMediaKeySystemConfiguration

instance IsGObject MediaKeySystemConfiguration where
  typeGType :: MediaKeySystemConfiguration -> JSM GType
typeGType MediaKeySystemConfiguration
_ = JSM GType
gTypeMediaKeySystemConfiguration
  {-# INLINE typeGType #-}

noMediaKeySystemConfiguration :: Maybe MediaKeySystemConfiguration
noMediaKeySystemConfiguration :: Maybe MediaKeySystemConfiguration
noMediaKeySystemConfiguration = Maybe MediaKeySystemConfiguration
forall a. Maybe a
Nothing
{-# INLINE noMediaKeySystemConfiguration #-}

gTypeMediaKeySystemConfiguration :: JSM GType
gTypeMediaKeySystemConfiguration :: JSM GType
gTypeMediaKeySystemConfiguration = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaKeySystemConfiguration"

-- | Functions for this inteface are in "JSDOM.MediaKeySystemMediaCapability".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaKeySystemMediaCapability Mozilla MediaKeySystemMediaCapability documentation>
newtype MediaKeySystemMediaCapability = MediaKeySystemMediaCapability { MediaKeySystemMediaCapability -> JSVal
unMediaKeySystemMediaCapability :: JSVal }

instance PToJSVal MediaKeySystemMediaCapability where
  pToJSVal :: MediaKeySystemMediaCapability -> JSVal
pToJSVal = MediaKeySystemMediaCapability -> JSVal
unMediaKeySystemMediaCapability
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaKeySystemMediaCapability where
  pFromJSVal :: JSVal -> MediaKeySystemMediaCapability
pFromJSVal = JSVal -> MediaKeySystemMediaCapability
MediaKeySystemMediaCapability
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaKeySystemMediaCapability where
  toJSVal :: MediaKeySystemMediaCapability -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaKeySystemMediaCapability -> JSVal)
-> MediaKeySystemMediaCapability
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeySystemMediaCapability -> JSVal
unMediaKeySystemMediaCapability
  {-# INLINE toJSVal #-}

instance FromJSVal MediaKeySystemMediaCapability where
  fromJSVal :: JSVal -> JSM (Maybe MediaKeySystemMediaCapability)
fromJSVal JSVal
v = (JSVal -> MediaKeySystemMediaCapability)
-> Maybe JSVal -> Maybe MediaKeySystemMediaCapability
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaKeySystemMediaCapability
MediaKeySystemMediaCapability (Maybe JSVal -> Maybe MediaKeySystemMediaCapability)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaKeySystemMediaCapability)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaKeySystemMediaCapability
fromJSValUnchecked = MediaKeySystemMediaCapability -> JSM MediaKeySystemMediaCapability
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeySystemMediaCapability
 -> JSM MediaKeySystemMediaCapability)
-> (JSVal -> MediaKeySystemMediaCapability)
-> JSVal
-> JSM MediaKeySystemMediaCapability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaKeySystemMediaCapability
MediaKeySystemMediaCapability
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaKeySystemMediaCapability where
  makeObject :: MediaKeySystemMediaCapability -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaKeySystemMediaCapability -> JSVal)
-> MediaKeySystemMediaCapability
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeySystemMediaCapability -> JSVal
unMediaKeySystemMediaCapability

instance IsGObject MediaKeySystemMediaCapability where
  typeGType :: MediaKeySystemMediaCapability -> JSM GType
typeGType MediaKeySystemMediaCapability
_ = JSM GType
gTypeMediaKeySystemMediaCapability
  {-# INLINE typeGType #-}

noMediaKeySystemMediaCapability :: Maybe MediaKeySystemMediaCapability
noMediaKeySystemMediaCapability :: Maybe MediaKeySystemMediaCapability
noMediaKeySystemMediaCapability = Maybe MediaKeySystemMediaCapability
forall a. Maybe a
Nothing
{-# INLINE noMediaKeySystemMediaCapability #-}

gTypeMediaKeySystemMediaCapability :: JSM GType
gTypeMediaKeySystemMediaCapability :: JSM GType
gTypeMediaKeySystemMediaCapability = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaKeySystemMediaCapability"

-- | Functions for this inteface are in "JSDOM.MediaKeys".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitMediaKeys Mozilla WebKitMediaKeys documentation>
newtype MediaKeys = MediaKeys { MediaKeys -> JSVal
unMediaKeys :: JSVal }

instance PToJSVal MediaKeys where
  pToJSVal :: MediaKeys -> JSVal
pToJSVal = MediaKeys -> JSVal
unMediaKeys
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaKeys where
  pFromJSVal :: JSVal -> MediaKeys
pFromJSVal = JSVal -> MediaKeys
MediaKeys
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaKeys where
  toJSVal :: MediaKeys -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaKeys -> JSVal) -> MediaKeys -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeys -> JSVal
unMediaKeys
  {-# INLINE toJSVal #-}

instance FromJSVal MediaKeys where
  fromJSVal :: JSVal -> JSM (Maybe MediaKeys)
fromJSVal JSVal
v = (JSVal -> MediaKeys) -> Maybe JSVal -> Maybe MediaKeys
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaKeys
MediaKeys (Maybe JSVal -> Maybe MediaKeys)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaKeys)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaKeys
fromJSValUnchecked = MediaKeys -> JSM MediaKeys
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeys -> JSM MediaKeys)
-> (JSVal -> MediaKeys) -> JSVal -> JSM MediaKeys
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaKeys
MediaKeys
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaKeys where
  makeObject :: MediaKeys -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaKeys -> JSVal) -> MediaKeys -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaKeys -> JSVal
unMediaKeys

instance IsGObject MediaKeys where
  typeGType :: MediaKeys -> JSM GType
typeGType MediaKeys
_ = JSM GType
gTypeMediaKeys
  {-# INLINE typeGType #-}

noMediaKeys :: Maybe MediaKeys
noMediaKeys :: Maybe MediaKeys
noMediaKeys = Maybe MediaKeys
forall a. Maybe a
Nothing
{-# INLINE noMediaKeys #-}

gTypeMediaKeys :: JSM GType
gTypeMediaKeys :: JSM GType
gTypeMediaKeys = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitMediaKeys"

-- | Functions for this inteface are in "JSDOM.MediaList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaList Mozilla MediaList documentation>
newtype MediaList = MediaList { MediaList -> JSVal
unMediaList :: JSVal }

instance PToJSVal MediaList where
  pToJSVal :: MediaList -> JSVal
pToJSVal = MediaList -> JSVal
unMediaList
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaList where
  pFromJSVal :: JSVal -> MediaList
pFromJSVal = JSVal -> MediaList
MediaList
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaList where
  toJSVal :: MediaList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaList -> JSVal) -> MediaList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaList -> JSVal
unMediaList
  {-# INLINE toJSVal #-}

instance FromJSVal MediaList where
  fromJSVal :: JSVal -> JSM (Maybe MediaList)
fromJSVal JSVal
v = (JSVal -> MediaList) -> Maybe JSVal -> Maybe MediaList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaList
MediaList (Maybe JSVal -> Maybe MediaList)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaList
fromJSValUnchecked = MediaList -> JSM MediaList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaList -> JSM MediaList)
-> (JSVal -> MediaList) -> JSVal -> JSM MediaList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaList
MediaList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaList where
  makeObject :: MediaList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaList -> JSVal) -> MediaList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaList -> JSVal
unMediaList

instance IsGObject MediaList where
  typeGType :: MediaList -> JSM GType
typeGType MediaList
_ = JSM GType
gTypeMediaList
  {-# INLINE typeGType #-}

noMediaList :: Maybe MediaList
noMediaList :: Maybe MediaList
noMediaList = Maybe MediaList
forall a. Maybe a
Nothing
{-# INLINE noMediaList #-}

gTypeMediaList :: JSM GType
gTypeMediaList :: JSM GType
gTypeMediaList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaList"

-- | Functions for this inteface are in "JSDOM.MediaMetadata".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaMetadata Mozilla MediaMetadata documentation>
newtype MediaMetadata = MediaMetadata { MediaMetadata -> JSVal
unMediaMetadata :: JSVal }

instance PToJSVal MediaMetadata where
  pToJSVal :: MediaMetadata -> JSVal
pToJSVal = MediaMetadata -> JSVal
unMediaMetadata
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaMetadata where
  pFromJSVal :: JSVal -> MediaMetadata
pFromJSVal = JSVal -> MediaMetadata
MediaMetadata
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaMetadata where
  toJSVal :: MediaMetadata -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaMetadata -> JSVal) -> MediaMetadata -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaMetadata -> JSVal
unMediaMetadata
  {-# INLINE toJSVal #-}

instance FromJSVal MediaMetadata where
  fromJSVal :: JSVal -> JSM (Maybe MediaMetadata)
fromJSVal JSVal
v = (JSVal -> MediaMetadata) -> Maybe JSVal -> Maybe MediaMetadata
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaMetadata
MediaMetadata (Maybe JSVal -> Maybe MediaMetadata)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaMetadata)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaMetadata
fromJSValUnchecked = MediaMetadata -> JSM MediaMetadata
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaMetadata -> JSM MediaMetadata)
-> (JSVal -> MediaMetadata) -> JSVal -> JSM MediaMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaMetadata
MediaMetadata
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaMetadata where
  makeObject :: MediaMetadata -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaMetadata -> JSVal) -> MediaMetadata -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaMetadata -> JSVal
unMediaMetadata

instance IsGObject MediaMetadata where
  typeGType :: MediaMetadata -> JSM GType
typeGType MediaMetadata
_ = JSM GType
gTypeMediaMetadata
  {-# INLINE typeGType #-}

noMediaMetadata :: Maybe MediaMetadata
noMediaMetadata :: Maybe MediaMetadata
noMediaMetadata = Maybe MediaMetadata
forall a. Maybe a
Nothing
{-# INLINE noMediaMetadata #-}

gTypeMediaMetadata :: JSM GType
gTypeMediaMetadata :: JSM GType
gTypeMediaMetadata = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaMetadata"

-- | Functions for this inteface are in "JSDOM.MediaQueryList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaQueryList Mozilla MediaQueryList documentation>
newtype MediaQueryList = MediaQueryList { MediaQueryList -> JSVal
unMediaQueryList :: JSVal }

instance PToJSVal MediaQueryList where
  pToJSVal :: MediaQueryList -> JSVal
pToJSVal = MediaQueryList -> JSVal
unMediaQueryList
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaQueryList where
  pFromJSVal :: JSVal -> MediaQueryList
pFromJSVal = JSVal -> MediaQueryList
MediaQueryList
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaQueryList where
  toJSVal :: MediaQueryList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaQueryList -> JSVal) -> MediaQueryList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaQueryList -> JSVal
unMediaQueryList
  {-# INLINE toJSVal #-}

instance FromJSVal MediaQueryList where
  fromJSVal :: JSVal -> JSM (Maybe MediaQueryList)
fromJSVal JSVal
v = (JSVal -> MediaQueryList) -> Maybe JSVal -> Maybe MediaQueryList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaQueryList
MediaQueryList (Maybe JSVal -> Maybe MediaQueryList)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaQueryList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaQueryList
fromJSValUnchecked = MediaQueryList -> JSM MediaQueryList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaQueryList -> JSM MediaQueryList)
-> (JSVal -> MediaQueryList) -> JSVal -> JSM MediaQueryList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaQueryList
MediaQueryList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaQueryList where
  makeObject :: MediaQueryList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaQueryList -> JSVal) -> MediaQueryList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaQueryList -> JSVal
unMediaQueryList

instance IsGObject MediaQueryList where
  typeGType :: MediaQueryList -> JSM GType
typeGType MediaQueryList
_ = JSM GType
gTypeMediaQueryList
  {-# INLINE typeGType #-}

noMediaQueryList :: Maybe MediaQueryList
noMediaQueryList :: Maybe MediaQueryList
noMediaQueryList = Maybe MediaQueryList
forall a. Maybe a
Nothing
{-# INLINE noMediaQueryList #-}

gTypeMediaQueryList :: JSM GType
gTypeMediaQueryList :: JSM GType
gTypeMediaQueryList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaQueryList"

-- | Functions for this inteface are in "JSDOM.MediaRemoteControls".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaRemoteControls Mozilla MediaRemoteControls documentation>
newtype MediaRemoteControls = MediaRemoteControls { MediaRemoteControls -> JSVal
unMediaRemoteControls :: JSVal }

instance PToJSVal MediaRemoteControls where
  pToJSVal :: MediaRemoteControls -> JSVal
pToJSVal = MediaRemoteControls -> JSVal
unMediaRemoteControls
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaRemoteControls where
  pFromJSVal :: JSVal -> MediaRemoteControls
pFromJSVal = JSVal -> MediaRemoteControls
MediaRemoteControls
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaRemoteControls where
  toJSVal :: MediaRemoteControls -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaRemoteControls -> JSVal)
-> MediaRemoteControls
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaRemoteControls -> JSVal
unMediaRemoteControls
  {-# INLINE toJSVal #-}

instance FromJSVal MediaRemoteControls where
  fromJSVal :: JSVal -> JSM (Maybe MediaRemoteControls)
fromJSVal JSVal
v = (JSVal -> MediaRemoteControls)
-> Maybe JSVal -> Maybe MediaRemoteControls
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaRemoteControls
MediaRemoteControls (Maybe JSVal -> Maybe MediaRemoteControls)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaRemoteControls)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaRemoteControls
fromJSValUnchecked = MediaRemoteControls -> JSM MediaRemoteControls
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaRemoteControls -> JSM MediaRemoteControls)
-> (JSVal -> MediaRemoteControls)
-> JSVal
-> JSM MediaRemoteControls
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaRemoteControls
MediaRemoteControls
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaRemoteControls where
  makeObject :: MediaRemoteControls -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaRemoteControls -> JSVal)
-> MediaRemoteControls
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaRemoteControls -> JSVal
unMediaRemoteControls

instance IsEventTarget MediaRemoteControls
instance IsGObject MediaRemoteControls where
  typeGType :: MediaRemoteControls -> JSM GType
typeGType MediaRemoteControls
_ = JSM GType
gTypeMediaRemoteControls
  {-# INLINE typeGType #-}

noMediaRemoteControls :: Maybe MediaRemoteControls
noMediaRemoteControls :: Maybe MediaRemoteControls
noMediaRemoteControls = Maybe MediaRemoteControls
forall a. Maybe a
Nothing
{-# INLINE noMediaRemoteControls #-}

gTypeMediaRemoteControls :: JSM GType
gTypeMediaRemoteControls :: JSM GType
gTypeMediaRemoteControls = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaRemoteControls"

-- | Functions for this inteface are in "JSDOM.MediaSession".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaSession Mozilla MediaSession documentation>
newtype MediaSession = MediaSession { MediaSession -> JSVal
unMediaSession :: JSVal }

instance PToJSVal MediaSession where
  pToJSVal :: MediaSession -> JSVal
pToJSVal = MediaSession -> JSVal
unMediaSession
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaSession where
  pFromJSVal :: JSVal -> MediaSession
pFromJSVal = JSVal -> MediaSession
MediaSession
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaSession where
  toJSVal :: MediaSession -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaSession -> JSVal) -> MediaSession -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaSession -> JSVal
unMediaSession
  {-# INLINE toJSVal #-}

instance FromJSVal MediaSession where
  fromJSVal :: JSVal -> JSM (Maybe MediaSession)
fromJSVal JSVal
v = (JSVal -> MediaSession) -> Maybe JSVal -> Maybe MediaSession
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaSession
MediaSession (Maybe JSVal -> Maybe MediaSession)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaSession)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaSession
fromJSValUnchecked = MediaSession -> JSM MediaSession
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaSession -> JSM MediaSession)
-> (JSVal -> MediaSession) -> JSVal -> JSM MediaSession
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaSession
MediaSession
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaSession where
  makeObject :: MediaSession -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaSession -> JSVal) -> MediaSession -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaSession -> JSVal
unMediaSession

instance IsGObject MediaSession where
  typeGType :: MediaSession -> JSM GType
typeGType MediaSession
_ = JSM GType
gTypeMediaSession
  {-# INLINE typeGType #-}

noMediaSession :: Maybe MediaSession
noMediaSession :: Maybe MediaSession
noMediaSession = Maybe MediaSession
forall a. Maybe a
Nothing
{-# INLINE noMediaSession #-}

gTypeMediaSession :: JSM GType
gTypeMediaSession :: JSM GType
gTypeMediaSession = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaSession"

-- | Functions for this inteface are in "JSDOM.MediaSource".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaSource Mozilla MediaSource documentation>
newtype MediaSource = MediaSource { MediaSource -> JSVal
unMediaSource :: JSVal }

instance PToJSVal MediaSource where
  pToJSVal :: MediaSource -> JSVal
pToJSVal = MediaSource -> JSVal
unMediaSource
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaSource where
  pFromJSVal :: JSVal -> MediaSource
pFromJSVal = JSVal -> MediaSource
MediaSource
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaSource where
  toJSVal :: MediaSource -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaSource -> JSVal) -> MediaSource -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaSource -> JSVal
unMediaSource
  {-# INLINE toJSVal #-}

instance FromJSVal MediaSource where
  fromJSVal :: JSVal -> JSM (Maybe MediaSource)
fromJSVal JSVal
v = (JSVal -> MediaSource) -> Maybe JSVal -> Maybe MediaSource
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaSource
MediaSource (Maybe JSVal -> Maybe MediaSource)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaSource
fromJSValUnchecked = MediaSource -> JSM MediaSource
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaSource -> JSM MediaSource)
-> (JSVal -> MediaSource) -> JSVal -> JSM MediaSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaSource
MediaSource
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaSource where
  makeObject :: MediaSource -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaSource -> JSVal) -> MediaSource -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaSource -> JSVal
unMediaSource

instance IsEventTarget MediaSource
instance IsGObject MediaSource where
  typeGType :: MediaSource -> JSM GType
typeGType MediaSource
_ = JSM GType
gTypeMediaSource
  {-# INLINE typeGType #-}

noMediaSource :: Maybe MediaSource
noMediaSource :: Maybe MediaSource
noMediaSource = Maybe MediaSource
forall a. Maybe a
Nothing
{-# INLINE noMediaSource #-}

gTypeMediaSource :: JSM GType
gTypeMediaSource :: JSM GType
gTypeMediaSource = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaSource"

-- | Functions for this inteface are in "JSDOM.MediaStream".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/webkitMediaStream Mozilla webkitMediaStream documentation>
newtype MediaStream = MediaStream { MediaStream -> JSVal
unMediaStream :: JSVal }

instance PToJSVal MediaStream where
  pToJSVal :: MediaStream -> JSVal
pToJSVal = MediaStream -> JSVal
unMediaStream
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaStream where
  pFromJSVal :: JSVal -> MediaStream
pFromJSVal = JSVal -> MediaStream
MediaStream
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaStream where
  toJSVal :: MediaStream -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaStream -> JSVal) -> MediaStream -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStream -> JSVal
unMediaStream
  {-# INLINE toJSVal #-}

instance FromJSVal MediaStream where
  fromJSVal :: JSVal -> JSM (Maybe MediaStream)
fromJSVal JSVal
v = (JSVal -> MediaStream) -> Maybe JSVal -> Maybe MediaStream
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaStream
MediaStream (Maybe JSVal -> Maybe MediaStream)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaStream)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaStream
fromJSValUnchecked = MediaStream -> JSM MediaStream
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStream -> JSM MediaStream)
-> (JSVal -> MediaStream) -> JSVal -> JSM MediaStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaStream
MediaStream
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaStream where
  makeObject :: MediaStream -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaStream -> JSVal) -> MediaStream -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStream -> JSVal
unMediaStream

instance IsEventTarget MediaStream
instance IsGObject MediaStream where
  typeGType :: MediaStream -> JSM GType
typeGType MediaStream
_ = JSM GType
gTypeMediaStream
  {-# INLINE typeGType #-}

noMediaStream :: Maybe MediaStream
noMediaStream :: Maybe MediaStream
noMediaStream = Maybe MediaStream
forall a. Maybe a
Nothing
{-# INLINE noMediaStream #-}

gTypeMediaStream :: JSM GType
gTypeMediaStream :: JSM GType
gTypeMediaStream = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"webkitMediaStream"

-- | Functions for this inteface are in "JSDOM.MediaStreamAudioDestinationNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaStreamAudioDestinationNode Mozilla MediaStreamAudioDestinationNode documentation>
newtype MediaStreamAudioDestinationNode = MediaStreamAudioDestinationNode { MediaStreamAudioDestinationNode -> JSVal
unMediaStreamAudioDestinationNode :: JSVal }

instance PToJSVal MediaStreamAudioDestinationNode where
  pToJSVal :: MediaStreamAudioDestinationNode -> JSVal
pToJSVal = MediaStreamAudioDestinationNode -> JSVal
unMediaStreamAudioDestinationNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaStreamAudioDestinationNode where
  pFromJSVal :: JSVal -> MediaStreamAudioDestinationNode
pFromJSVal = JSVal -> MediaStreamAudioDestinationNode
MediaStreamAudioDestinationNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaStreamAudioDestinationNode where
  toJSVal :: MediaStreamAudioDestinationNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaStreamAudioDestinationNode -> JSVal)
-> MediaStreamAudioDestinationNode
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamAudioDestinationNode -> JSVal
unMediaStreamAudioDestinationNode
  {-# INLINE toJSVal #-}

instance FromJSVal MediaStreamAudioDestinationNode where
  fromJSVal :: JSVal -> JSM (Maybe MediaStreamAudioDestinationNode)
fromJSVal JSVal
v = (JSVal -> MediaStreamAudioDestinationNode)
-> Maybe JSVal -> Maybe MediaStreamAudioDestinationNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaStreamAudioDestinationNode
MediaStreamAudioDestinationNode (Maybe JSVal -> Maybe MediaStreamAudioDestinationNode)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaStreamAudioDestinationNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaStreamAudioDestinationNode
fromJSValUnchecked = MediaStreamAudioDestinationNode
-> JSM MediaStreamAudioDestinationNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStreamAudioDestinationNode
 -> JSM MediaStreamAudioDestinationNode)
-> (JSVal -> MediaStreamAudioDestinationNode)
-> JSVal
-> JSM MediaStreamAudioDestinationNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaStreamAudioDestinationNode
MediaStreamAudioDestinationNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaStreamAudioDestinationNode where
  makeObject :: MediaStreamAudioDestinationNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaStreamAudioDestinationNode -> JSVal)
-> MediaStreamAudioDestinationNode
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamAudioDestinationNode -> JSVal
unMediaStreamAudioDestinationNode

instance IsAudioNode MediaStreamAudioDestinationNode
instance IsEventTarget MediaStreamAudioDestinationNode
instance IsGObject MediaStreamAudioDestinationNode where
  typeGType :: MediaStreamAudioDestinationNode -> JSM GType
typeGType MediaStreamAudioDestinationNode
_ = JSM GType
gTypeMediaStreamAudioDestinationNode
  {-# INLINE typeGType #-}

noMediaStreamAudioDestinationNode :: Maybe MediaStreamAudioDestinationNode
noMediaStreamAudioDestinationNode :: Maybe MediaStreamAudioDestinationNode
noMediaStreamAudioDestinationNode = Maybe MediaStreamAudioDestinationNode
forall a. Maybe a
Nothing
{-# INLINE noMediaStreamAudioDestinationNode #-}

gTypeMediaStreamAudioDestinationNode :: JSM GType
gTypeMediaStreamAudioDestinationNode :: JSM GType
gTypeMediaStreamAudioDestinationNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaStreamAudioDestinationNode"

-- | Functions for this inteface are in "JSDOM.MediaStreamAudioSourceNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaStreamAudioSourceNode Mozilla MediaStreamAudioSourceNode documentation>
newtype MediaStreamAudioSourceNode = MediaStreamAudioSourceNode { MediaStreamAudioSourceNode -> JSVal
unMediaStreamAudioSourceNode :: JSVal }

instance PToJSVal MediaStreamAudioSourceNode where
  pToJSVal :: MediaStreamAudioSourceNode -> JSVal
pToJSVal = MediaStreamAudioSourceNode -> JSVal
unMediaStreamAudioSourceNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaStreamAudioSourceNode where
  pFromJSVal :: JSVal -> MediaStreamAudioSourceNode
pFromJSVal = JSVal -> MediaStreamAudioSourceNode
MediaStreamAudioSourceNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaStreamAudioSourceNode where
  toJSVal :: MediaStreamAudioSourceNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaStreamAudioSourceNode -> JSVal)
-> MediaStreamAudioSourceNode
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamAudioSourceNode -> JSVal
unMediaStreamAudioSourceNode
  {-# INLINE toJSVal #-}

instance FromJSVal MediaStreamAudioSourceNode where
  fromJSVal :: JSVal -> JSM (Maybe MediaStreamAudioSourceNode)
fromJSVal JSVal
v = (JSVal -> MediaStreamAudioSourceNode)
-> Maybe JSVal -> Maybe MediaStreamAudioSourceNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaStreamAudioSourceNode
MediaStreamAudioSourceNode (Maybe JSVal -> Maybe MediaStreamAudioSourceNode)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaStreamAudioSourceNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaStreamAudioSourceNode
fromJSValUnchecked = MediaStreamAudioSourceNode -> JSM MediaStreamAudioSourceNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStreamAudioSourceNode -> JSM MediaStreamAudioSourceNode)
-> (JSVal -> MediaStreamAudioSourceNode)
-> JSVal
-> JSM MediaStreamAudioSourceNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaStreamAudioSourceNode
MediaStreamAudioSourceNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaStreamAudioSourceNode where
  makeObject :: MediaStreamAudioSourceNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaStreamAudioSourceNode -> JSVal)
-> MediaStreamAudioSourceNode
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamAudioSourceNode -> JSVal
unMediaStreamAudioSourceNode

instance IsAudioNode MediaStreamAudioSourceNode
instance IsEventTarget MediaStreamAudioSourceNode
instance IsGObject MediaStreamAudioSourceNode where
  typeGType :: MediaStreamAudioSourceNode -> JSM GType
typeGType MediaStreamAudioSourceNode
_ = JSM GType
gTypeMediaStreamAudioSourceNode
  {-# INLINE typeGType #-}

noMediaStreamAudioSourceNode :: Maybe MediaStreamAudioSourceNode
noMediaStreamAudioSourceNode :: Maybe MediaStreamAudioSourceNode
noMediaStreamAudioSourceNode = Maybe MediaStreamAudioSourceNode
forall a. Maybe a
Nothing
{-# INLINE noMediaStreamAudioSourceNode #-}

gTypeMediaStreamAudioSourceNode :: JSM GType
gTypeMediaStreamAudioSourceNode :: JSM GType
gTypeMediaStreamAudioSourceNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaStreamAudioSourceNode"

-- | Functions for this inteface are in "JSDOM.MediaStreamConstraints".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaStreamConstraints Mozilla MediaStreamConstraints documentation>
newtype MediaStreamConstraints = MediaStreamConstraints { MediaStreamConstraints -> JSVal
unMediaStreamConstraints :: JSVal }

instance PToJSVal MediaStreamConstraints where
  pToJSVal :: MediaStreamConstraints -> JSVal
pToJSVal = MediaStreamConstraints -> JSVal
unMediaStreamConstraints
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaStreamConstraints where
  pFromJSVal :: JSVal -> MediaStreamConstraints
pFromJSVal = JSVal -> MediaStreamConstraints
MediaStreamConstraints
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaStreamConstraints where
  toJSVal :: MediaStreamConstraints -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaStreamConstraints -> JSVal)
-> MediaStreamConstraints
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamConstraints -> JSVal
unMediaStreamConstraints
  {-# INLINE toJSVal #-}

instance FromJSVal MediaStreamConstraints where
  fromJSVal :: JSVal -> JSM (Maybe MediaStreamConstraints)
fromJSVal JSVal
v = (JSVal -> MediaStreamConstraints)
-> Maybe JSVal -> Maybe MediaStreamConstraints
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaStreamConstraints
MediaStreamConstraints (Maybe JSVal -> Maybe MediaStreamConstraints)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaStreamConstraints)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaStreamConstraints
fromJSValUnchecked = MediaStreamConstraints -> JSM MediaStreamConstraints
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStreamConstraints -> JSM MediaStreamConstraints)
-> (JSVal -> MediaStreamConstraints)
-> JSVal
-> JSM MediaStreamConstraints
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaStreamConstraints
MediaStreamConstraints
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaStreamConstraints where
  makeObject :: MediaStreamConstraints -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaStreamConstraints -> JSVal)
-> MediaStreamConstraints
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamConstraints -> JSVal
unMediaStreamConstraints

instance IsGObject MediaStreamConstraints where
  typeGType :: MediaStreamConstraints -> JSM GType
typeGType MediaStreamConstraints
_ = JSM GType
gTypeMediaStreamConstraints
  {-# INLINE typeGType #-}

noMediaStreamConstraints :: Maybe MediaStreamConstraints
noMediaStreamConstraints :: Maybe MediaStreamConstraints
noMediaStreamConstraints = Maybe MediaStreamConstraints
forall a. Maybe a
Nothing
{-# INLINE noMediaStreamConstraints #-}

gTypeMediaStreamConstraints :: JSM GType
gTypeMediaStreamConstraints :: JSM GType
gTypeMediaStreamConstraints = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaStreamConstraints"

-- | Functions for this inteface are in "JSDOM.MediaStreamEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaStreamEvent Mozilla MediaStreamEvent documentation>
newtype MediaStreamEvent = MediaStreamEvent { MediaStreamEvent -> JSVal
unMediaStreamEvent :: JSVal }

instance PToJSVal MediaStreamEvent where
  pToJSVal :: MediaStreamEvent -> JSVal
pToJSVal = MediaStreamEvent -> JSVal
unMediaStreamEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaStreamEvent where
  pFromJSVal :: JSVal -> MediaStreamEvent
pFromJSVal = JSVal -> MediaStreamEvent
MediaStreamEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaStreamEvent where
  toJSVal :: MediaStreamEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaStreamEvent -> JSVal) -> MediaStreamEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamEvent -> JSVal
unMediaStreamEvent
  {-# INLINE toJSVal #-}

instance FromJSVal MediaStreamEvent where
  fromJSVal :: JSVal -> JSM (Maybe MediaStreamEvent)
fromJSVal JSVal
v = (JSVal -> MediaStreamEvent)
-> Maybe JSVal -> Maybe MediaStreamEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaStreamEvent
MediaStreamEvent (Maybe JSVal -> Maybe MediaStreamEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaStreamEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaStreamEvent
fromJSValUnchecked = MediaStreamEvent -> JSM MediaStreamEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStreamEvent -> JSM MediaStreamEvent)
-> (JSVal -> MediaStreamEvent) -> JSVal -> JSM MediaStreamEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaStreamEvent
MediaStreamEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaStreamEvent where
  makeObject :: MediaStreamEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaStreamEvent -> JSVal) -> MediaStreamEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamEvent -> JSVal
unMediaStreamEvent

instance IsEvent MediaStreamEvent
instance IsGObject MediaStreamEvent where
  typeGType :: MediaStreamEvent -> JSM GType
typeGType MediaStreamEvent
_ = JSM GType
gTypeMediaStreamEvent
  {-# INLINE typeGType #-}

noMediaStreamEvent :: Maybe MediaStreamEvent
noMediaStreamEvent :: Maybe MediaStreamEvent
noMediaStreamEvent = Maybe MediaStreamEvent
forall a. Maybe a
Nothing
{-# INLINE noMediaStreamEvent #-}

gTypeMediaStreamEvent :: JSM GType
gTypeMediaStreamEvent :: JSM GType
gTypeMediaStreamEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaStreamEvent"

-- | Functions for this inteface are in "JSDOM.MediaStreamEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaStreamEventInit Mozilla MediaStreamEventInit documentation>
newtype MediaStreamEventInit = MediaStreamEventInit { MediaStreamEventInit -> JSVal
unMediaStreamEventInit :: JSVal }

instance PToJSVal MediaStreamEventInit where
  pToJSVal :: MediaStreamEventInit -> JSVal
pToJSVal = MediaStreamEventInit -> JSVal
unMediaStreamEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaStreamEventInit where
  pFromJSVal :: JSVal -> MediaStreamEventInit
pFromJSVal = JSVal -> MediaStreamEventInit
MediaStreamEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaStreamEventInit where
  toJSVal :: MediaStreamEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaStreamEventInit -> JSVal)
-> MediaStreamEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamEventInit -> JSVal
unMediaStreamEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal MediaStreamEventInit where
  fromJSVal :: JSVal -> JSM (Maybe MediaStreamEventInit)
fromJSVal JSVal
v = (JSVal -> MediaStreamEventInit)
-> Maybe JSVal -> Maybe MediaStreamEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaStreamEventInit
MediaStreamEventInit (Maybe JSVal -> Maybe MediaStreamEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaStreamEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaStreamEventInit
fromJSValUnchecked = MediaStreamEventInit -> JSM MediaStreamEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStreamEventInit -> JSM MediaStreamEventInit)
-> (JSVal -> MediaStreamEventInit)
-> JSVal
-> JSM MediaStreamEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaStreamEventInit
MediaStreamEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaStreamEventInit where
  makeObject :: MediaStreamEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaStreamEventInit -> JSVal)
-> MediaStreamEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamEventInit -> JSVal
unMediaStreamEventInit

instance IsEventInit MediaStreamEventInit
instance IsGObject MediaStreamEventInit where
  typeGType :: MediaStreamEventInit -> JSM GType
typeGType MediaStreamEventInit
_ = JSM GType
gTypeMediaStreamEventInit
  {-# INLINE typeGType #-}

noMediaStreamEventInit :: Maybe MediaStreamEventInit
noMediaStreamEventInit :: Maybe MediaStreamEventInit
noMediaStreamEventInit = Maybe MediaStreamEventInit
forall a. Maybe a
Nothing
{-# INLINE noMediaStreamEventInit #-}

gTypeMediaStreamEventInit :: JSM GType
gTypeMediaStreamEventInit :: JSM GType
gTypeMediaStreamEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaStreamEventInit"

-- | Functions for this inteface are in "JSDOM.MediaStreamTrack".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaStreamTrack Mozilla MediaStreamTrack documentation>
newtype MediaStreamTrack = MediaStreamTrack { MediaStreamTrack -> JSVal
unMediaStreamTrack :: JSVal }

instance PToJSVal MediaStreamTrack where
  pToJSVal :: MediaStreamTrack -> JSVal
pToJSVal = MediaStreamTrack -> JSVal
unMediaStreamTrack
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaStreamTrack where
  pFromJSVal :: JSVal -> MediaStreamTrack
pFromJSVal = JSVal -> MediaStreamTrack
MediaStreamTrack
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaStreamTrack where
  toJSVal :: MediaStreamTrack -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaStreamTrack -> JSVal) -> MediaStreamTrack -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamTrack -> JSVal
unMediaStreamTrack
  {-# INLINE toJSVal #-}

instance FromJSVal MediaStreamTrack where
  fromJSVal :: JSVal -> JSM (Maybe MediaStreamTrack)
fromJSVal JSVal
v = (JSVal -> MediaStreamTrack)
-> Maybe JSVal -> Maybe MediaStreamTrack
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaStreamTrack
MediaStreamTrack (Maybe JSVal -> Maybe MediaStreamTrack)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaStreamTrack)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaStreamTrack
fromJSValUnchecked = MediaStreamTrack -> JSM MediaStreamTrack
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStreamTrack -> JSM MediaStreamTrack)
-> (JSVal -> MediaStreamTrack) -> JSVal -> JSM MediaStreamTrack
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaStreamTrack
MediaStreamTrack
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaStreamTrack where
  makeObject :: MediaStreamTrack -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaStreamTrack -> JSVal) -> MediaStreamTrack -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamTrack -> JSVal
unMediaStreamTrack

class (IsEventTarget o, IsGObject o) => IsMediaStreamTrack o
toMediaStreamTrack :: IsMediaStreamTrack o => o -> MediaStreamTrack
toMediaStreamTrack :: forall o. IsMediaStreamTrack o => o -> MediaStreamTrack
toMediaStreamTrack = JSVal -> MediaStreamTrack
MediaStreamTrack (JSVal -> MediaStreamTrack)
-> (o -> JSVal) -> o -> MediaStreamTrack
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsMediaStreamTrack MediaStreamTrack
instance IsEventTarget MediaStreamTrack
instance IsGObject MediaStreamTrack where
  typeGType :: MediaStreamTrack -> JSM GType
typeGType MediaStreamTrack
_ = JSM GType
gTypeMediaStreamTrack
  {-# INLINE typeGType #-}

noMediaStreamTrack :: Maybe MediaStreamTrack
noMediaStreamTrack :: Maybe MediaStreamTrack
noMediaStreamTrack = Maybe MediaStreamTrack
forall a. Maybe a
Nothing
{-# INLINE noMediaStreamTrack #-}

gTypeMediaStreamTrack :: JSM GType
gTypeMediaStreamTrack :: JSM GType
gTypeMediaStreamTrack = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaStreamTrack"

-- | Functions for this inteface are in "JSDOM.MediaStreamTrackEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaStreamTrackEvent Mozilla MediaStreamTrackEvent documentation>
newtype MediaStreamTrackEvent = MediaStreamTrackEvent { MediaStreamTrackEvent -> JSVal
unMediaStreamTrackEvent :: JSVal }

instance PToJSVal MediaStreamTrackEvent where
  pToJSVal :: MediaStreamTrackEvent -> JSVal
pToJSVal = MediaStreamTrackEvent -> JSVal
unMediaStreamTrackEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaStreamTrackEvent where
  pFromJSVal :: JSVal -> MediaStreamTrackEvent
pFromJSVal = JSVal -> MediaStreamTrackEvent
MediaStreamTrackEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaStreamTrackEvent where
  toJSVal :: MediaStreamTrackEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaStreamTrackEvent -> JSVal)
-> MediaStreamTrackEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamTrackEvent -> JSVal
unMediaStreamTrackEvent
  {-# INLINE toJSVal #-}

instance FromJSVal MediaStreamTrackEvent where
  fromJSVal :: JSVal -> JSM (Maybe MediaStreamTrackEvent)
fromJSVal JSVal
v = (JSVal -> MediaStreamTrackEvent)
-> Maybe JSVal -> Maybe MediaStreamTrackEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaStreamTrackEvent
MediaStreamTrackEvent (Maybe JSVal -> Maybe MediaStreamTrackEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaStreamTrackEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaStreamTrackEvent
fromJSValUnchecked = MediaStreamTrackEvent -> JSM MediaStreamTrackEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStreamTrackEvent -> JSM MediaStreamTrackEvent)
-> (JSVal -> MediaStreamTrackEvent)
-> JSVal
-> JSM MediaStreamTrackEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaStreamTrackEvent
MediaStreamTrackEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaStreamTrackEvent where
  makeObject :: MediaStreamTrackEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaStreamTrackEvent -> JSVal)
-> MediaStreamTrackEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamTrackEvent -> JSVal
unMediaStreamTrackEvent

instance IsEvent MediaStreamTrackEvent
instance IsGObject MediaStreamTrackEvent where
  typeGType :: MediaStreamTrackEvent -> JSM GType
typeGType MediaStreamTrackEvent
_ = JSM GType
gTypeMediaStreamTrackEvent
  {-# INLINE typeGType #-}

noMediaStreamTrackEvent :: Maybe MediaStreamTrackEvent
noMediaStreamTrackEvent :: Maybe MediaStreamTrackEvent
noMediaStreamTrackEvent = Maybe MediaStreamTrackEvent
forall a. Maybe a
Nothing
{-# INLINE noMediaStreamTrackEvent #-}

gTypeMediaStreamTrackEvent :: JSM GType
gTypeMediaStreamTrackEvent :: JSM GType
gTypeMediaStreamTrackEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaStreamTrackEvent"

-- | Functions for this inteface are in "JSDOM.MediaStreamTrackEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaStreamTrackEventInit Mozilla MediaStreamTrackEventInit documentation>
newtype MediaStreamTrackEventInit = MediaStreamTrackEventInit { MediaStreamTrackEventInit -> JSVal
unMediaStreamTrackEventInit :: JSVal }

instance PToJSVal MediaStreamTrackEventInit where
  pToJSVal :: MediaStreamTrackEventInit -> JSVal
pToJSVal = MediaStreamTrackEventInit -> JSVal
unMediaStreamTrackEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaStreamTrackEventInit where
  pFromJSVal :: JSVal -> MediaStreamTrackEventInit
pFromJSVal = JSVal -> MediaStreamTrackEventInit
MediaStreamTrackEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaStreamTrackEventInit where
  toJSVal :: MediaStreamTrackEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaStreamTrackEventInit -> JSVal)
-> MediaStreamTrackEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamTrackEventInit -> JSVal
unMediaStreamTrackEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal MediaStreamTrackEventInit where
  fromJSVal :: JSVal -> JSM (Maybe MediaStreamTrackEventInit)
fromJSVal JSVal
v = (JSVal -> MediaStreamTrackEventInit)
-> Maybe JSVal -> Maybe MediaStreamTrackEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaStreamTrackEventInit
MediaStreamTrackEventInit (Maybe JSVal -> Maybe MediaStreamTrackEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaStreamTrackEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaStreamTrackEventInit
fromJSValUnchecked = MediaStreamTrackEventInit -> JSM MediaStreamTrackEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStreamTrackEventInit -> JSM MediaStreamTrackEventInit)
-> (JSVal -> MediaStreamTrackEventInit)
-> JSVal
-> JSM MediaStreamTrackEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaStreamTrackEventInit
MediaStreamTrackEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaStreamTrackEventInit where
  makeObject :: MediaStreamTrackEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaStreamTrackEventInit -> JSVal)
-> MediaStreamTrackEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaStreamTrackEventInit -> JSVal
unMediaStreamTrackEventInit

instance IsEventInit MediaStreamTrackEventInit
instance IsGObject MediaStreamTrackEventInit where
  typeGType :: MediaStreamTrackEventInit -> JSM GType
typeGType MediaStreamTrackEventInit
_ = JSM GType
gTypeMediaStreamTrackEventInit
  {-# INLINE typeGType #-}

noMediaStreamTrackEventInit :: Maybe MediaStreamTrackEventInit
noMediaStreamTrackEventInit :: Maybe MediaStreamTrackEventInit
noMediaStreamTrackEventInit = Maybe MediaStreamTrackEventInit
forall a. Maybe a
Nothing
{-# INLINE noMediaStreamTrackEventInit #-}

gTypeMediaStreamTrackEventInit :: JSM GType
gTypeMediaStreamTrackEventInit :: JSM GType
gTypeMediaStreamTrackEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaStreamTrackEventInit"

-- | Functions for this inteface are in "JSDOM.MediaTrackCapabilities".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaTrackCapabilities Mozilla MediaTrackCapabilities documentation>
newtype MediaTrackCapabilities = MediaTrackCapabilities { MediaTrackCapabilities -> JSVal
unMediaTrackCapabilities :: JSVal }

instance PToJSVal MediaTrackCapabilities where
  pToJSVal :: MediaTrackCapabilities -> JSVal
pToJSVal = MediaTrackCapabilities -> JSVal
unMediaTrackCapabilities
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaTrackCapabilities where
  pFromJSVal :: JSVal -> MediaTrackCapabilities
pFromJSVal = JSVal -> MediaTrackCapabilities
MediaTrackCapabilities
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaTrackCapabilities where
  toJSVal :: MediaTrackCapabilities -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaTrackCapabilities -> JSVal)
-> MediaTrackCapabilities
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaTrackCapabilities -> JSVal
unMediaTrackCapabilities
  {-# INLINE toJSVal #-}

instance FromJSVal MediaTrackCapabilities where
  fromJSVal :: JSVal -> JSM (Maybe MediaTrackCapabilities)
fromJSVal JSVal
v = (JSVal -> MediaTrackCapabilities)
-> Maybe JSVal -> Maybe MediaTrackCapabilities
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaTrackCapabilities
MediaTrackCapabilities (Maybe JSVal -> Maybe MediaTrackCapabilities)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaTrackCapabilities)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaTrackCapabilities
fromJSValUnchecked = MediaTrackCapabilities -> JSM MediaTrackCapabilities
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaTrackCapabilities -> JSM MediaTrackCapabilities)
-> (JSVal -> MediaTrackCapabilities)
-> JSVal
-> JSM MediaTrackCapabilities
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaTrackCapabilities
MediaTrackCapabilities
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaTrackCapabilities where
  makeObject :: MediaTrackCapabilities -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaTrackCapabilities -> JSVal)
-> MediaTrackCapabilities
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaTrackCapabilities -> JSVal
unMediaTrackCapabilities

instance IsGObject MediaTrackCapabilities where
  typeGType :: MediaTrackCapabilities -> JSM GType
typeGType MediaTrackCapabilities
_ = JSM GType
gTypeMediaTrackCapabilities
  {-# INLINE typeGType #-}

noMediaTrackCapabilities :: Maybe MediaTrackCapabilities
noMediaTrackCapabilities :: Maybe MediaTrackCapabilities
noMediaTrackCapabilities = Maybe MediaTrackCapabilities
forall a. Maybe a
Nothing
{-# INLINE noMediaTrackCapabilities #-}

gTypeMediaTrackCapabilities :: JSM GType
gTypeMediaTrackCapabilities :: JSM GType
gTypeMediaTrackCapabilities = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaTrackCapabilities"

-- | Functions for this inteface are in "JSDOM.MediaTrackConstraintSet".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaTrackConstraintSet Mozilla MediaTrackConstraintSet documentation>
newtype MediaTrackConstraintSet = MediaTrackConstraintSet { MediaTrackConstraintSet -> JSVal
unMediaTrackConstraintSet :: JSVal }

instance PToJSVal MediaTrackConstraintSet where
  pToJSVal :: MediaTrackConstraintSet -> JSVal
pToJSVal = MediaTrackConstraintSet -> JSVal
unMediaTrackConstraintSet
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaTrackConstraintSet where
  pFromJSVal :: JSVal -> MediaTrackConstraintSet
pFromJSVal = JSVal -> MediaTrackConstraintSet
MediaTrackConstraintSet
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaTrackConstraintSet where
  toJSVal :: MediaTrackConstraintSet -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaTrackConstraintSet -> JSVal)
-> MediaTrackConstraintSet
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaTrackConstraintSet -> JSVal
unMediaTrackConstraintSet
  {-# INLINE toJSVal #-}

instance FromJSVal MediaTrackConstraintSet where
  fromJSVal :: JSVal -> JSM (Maybe MediaTrackConstraintSet)
fromJSVal JSVal
v = (JSVal -> MediaTrackConstraintSet)
-> Maybe JSVal -> Maybe MediaTrackConstraintSet
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaTrackConstraintSet
MediaTrackConstraintSet (Maybe JSVal -> Maybe MediaTrackConstraintSet)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaTrackConstraintSet)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaTrackConstraintSet
fromJSValUnchecked = MediaTrackConstraintSet -> JSM MediaTrackConstraintSet
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaTrackConstraintSet -> JSM MediaTrackConstraintSet)
-> (JSVal -> MediaTrackConstraintSet)
-> JSVal
-> JSM MediaTrackConstraintSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaTrackConstraintSet
MediaTrackConstraintSet
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaTrackConstraintSet where
  makeObject :: MediaTrackConstraintSet -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaTrackConstraintSet -> JSVal)
-> MediaTrackConstraintSet
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaTrackConstraintSet -> JSVal
unMediaTrackConstraintSet

class (IsGObject o) => IsMediaTrackConstraintSet o
toMediaTrackConstraintSet :: IsMediaTrackConstraintSet o => o -> MediaTrackConstraintSet
toMediaTrackConstraintSet :: forall o.
IsMediaTrackConstraintSet o =>
o -> MediaTrackConstraintSet
toMediaTrackConstraintSet = JSVal -> MediaTrackConstraintSet
MediaTrackConstraintSet (JSVal -> MediaTrackConstraintSet)
-> (o -> JSVal) -> o -> MediaTrackConstraintSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsMediaTrackConstraintSet MediaTrackConstraintSet
instance IsGObject MediaTrackConstraintSet where
  typeGType :: MediaTrackConstraintSet -> JSM GType
typeGType MediaTrackConstraintSet
_ = JSM GType
gTypeMediaTrackConstraintSet
  {-# INLINE typeGType #-}

noMediaTrackConstraintSet :: Maybe MediaTrackConstraintSet
noMediaTrackConstraintSet :: Maybe MediaTrackConstraintSet
noMediaTrackConstraintSet = Maybe MediaTrackConstraintSet
forall a. Maybe a
Nothing
{-# INLINE noMediaTrackConstraintSet #-}

gTypeMediaTrackConstraintSet :: JSM GType
gTypeMediaTrackConstraintSet :: JSM GType
gTypeMediaTrackConstraintSet = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaTrackConstraintSet"

-- | Functions for this inteface are in "JSDOM.MediaTrackConstraints".
-- Base interface functions are in:
--
--     * "JSDOM.MediaTrackConstraintSet"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaTrackConstraints Mozilla MediaTrackConstraints documentation>
newtype MediaTrackConstraints = MediaTrackConstraints { MediaTrackConstraints -> JSVal
unMediaTrackConstraints :: JSVal }

instance PToJSVal MediaTrackConstraints where
  pToJSVal :: MediaTrackConstraints -> JSVal
pToJSVal = MediaTrackConstraints -> JSVal
unMediaTrackConstraints
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaTrackConstraints where
  pFromJSVal :: JSVal -> MediaTrackConstraints
pFromJSVal = JSVal -> MediaTrackConstraints
MediaTrackConstraints
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaTrackConstraints where
  toJSVal :: MediaTrackConstraints -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaTrackConstraints -> JSVal)
-> MediaTrackConstraints
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaTrackConstraints -> JSVal
unMediaTrackConstraints
  {-# INLINE toJSVal #-}

instance FromJSVal MediaTrackConstraints where
  fromJSVal :: JSVal -> JSM (Maybe MediaTrackConstraints)
fromJSVal JSVal
v = (JSVal -> MediaTrackConstraints)
-> Maybe JSVal -> Maybe MediaTrackConstraints
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaTrackConstraints
MediaTrackConstraints (Maybe JSVal -> Maybe MediaTrackConstraints)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaTrackConstraints)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaTrackConstraints
fromJSValUnchecked = MediaTrackConstraints -> JSM MediaTrackConstraints
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaTrackConstraints -> JSM MediaTrackConstraints)
-> (JSVal -> MediaTrackConstraints)
-> JSVal
-> JSM MediaTrackConstraints
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaTrackConstraints
MediaTrackConstraints
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaTrackConstraints where
  makeObject :: MediaTrackConstraints -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaTrackConstraints -> JSVal)
-> MediaTrackConstraints
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaTrackConstraints -> JSVal
unMediaTrackConstraints

instance IsMediaTrackConstraintSet MediaTrackConstraints
instance IsGObject MediaTrackConstraints where
  typeGType :: MediaTrackConstraints -> JSM GType
typeGType MediaTrackConstraints
_ = JSM GType
gTypeMediaTrackConstraints
  {-# INLINE typeGType #-}

noMediaTrackConstraints :: Maybe MediaTrackConstraints
noMediaTrackConstraints :: Maybe MediaTrackConstraints
noMediaTrackConstraints = Maybe MediaTrackConstraints
forall a. Maybe a
Nothing
{-# INLINE noMediaTrackConstraints #-}

gTypeMediaTrackConstraints :: JSM GType
gTypeMediaTrackConstraints :: JSM GType
gTypeMediaTrackConstraints = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaTrackConstraints"

-- | Functions for this inteface are in "JSDOM.MediaTrackSettings".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaTrackSettings Mozilla MediaTrackSettings documentation>
newtype MediaTrackSettings = MediaTrackSettings { MediaTrackSettings -> JSVal
unMediaTrackSettings :: JSVal }

instance PToJSVal MediaTrackSettings where
  pToJSVal :: MediaTrackSettings -> JSVal
pToJSVal = MediaTrackSettings -> JSVal
unMediaTrackSettings
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaTrackSettings where
  pFromJSVal :: JSVal -> MediaTrackSettings
pFromJSVal = JSVal -> MediaTrackSettings
MediaTrackSettings
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaTrackSettings where
  toJSVal :: MediaTrackSettings -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaTrackSettings -> JSVal) -> MediaTrackSettings -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaTrackSettings -> JSVal
unMediaTrackSettings
  {-# INLINE toJSVal #-}

instance FromJSVal MediaTrackSettings where
  fromJSVal :: JSVal -> JSM (Maybe MediaTrackSettings)
fromJSVal JSVal
v = (JSVal -> MediaTrackSettings)
-> Maybe JSVal -> Maybe MediaTrackSettings
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaTrackSettings
MediaTrackSettings (Maybe JSVal -> Maybe MediaTrackSettings)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaTrackSettings)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaTrackSettings
fromJSValUnchecked = MediaTrackSettings -> JSM MediaTrackSettings
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaTrackSettings -> JSM MediaTrackSettings)
-> (JSVal -> MediaTrackSettings) -> JSVal -> JSM MediaTrackSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaTrackSettings
MediaTrackSettings
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaTrackSettings where
  makeObject :: MediaTrackSettings -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaTrackSettings -> JSVal)
-> MediaTrackSettings
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaTrackSettings -> JSVal
unMediaTrackSettings

instance IsGObject MediaTrackSettings where
  typeGType :: MediaTrackSettings -> JSM GType
typeGType MediaTrackSettings
_ = JSM GType
gTypeMediaTrackSettings
  {-# INLINE typeGType #-}

noMediaTrackSettings :: Maybe MediaTrackSettings
noMediaTrackSettings :: Maybe MediaTrackSettings
noMediaTrackSettings = Maybe MediaTrackSettings
forall a. Maybe a
Nothing
{-# INLINE noMediaTrackSettings #-}

gTypeMediaTrackSettings :: JSM GType
gTypeMediaTrackSettings :: JSM GType
gTypeMediaTrackSettings = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaTrackSettings"

-- | Functions for this inteface are in "JSDOM.MediaTrackSupportedConstraints".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MediaTrackSupportedConstraints Mozilla MediaTrackSupportedConstraints documentation>
newtype MediaTrackSupportedConstraints = MediaTrackSupportedConstraints { MediaTrackSupportedConstraints -> JSVal
unMediaTrackSupportedConstraints :: JSVal }

instance PToJSVal MediaTrackSupportedConstraints where
  pToJSVal :: MediaTrackSupportedConstraints -> JSVal
pToJSVal = MediaTrackSupportedConstraints -> JSVal
unMediaTrackSupportedConstraints
  {-# INLINE pToJSVal #-}

instance PFromJSVal MediaTrackSupportedConstraints where
  pFromJSVal :: JSVal -> MediaTrackSupportedConstraints
pFromJSVal = JSVal -> MediaTrackSupportedConstraints
MediaTrackSupportedConstraints
  {-# INLINE pFromJSVal #-}

instance ToJSVal MediaTrackSupportedConstraints where
  toJSVal :: MediaTrackSupportedConstraints -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MediaTrackSupportedConstraints -> JSVal)
-> MediaTrackSupportedConstraints
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaTrackSupportedConstraints -> JSVal
unMediaTrackSupportedConstraints
  {-# INLINE toJSVal #-}

instance FromJSVal MediaTrackSupportedConstraints where
  fromJSVal :: JSVal -> JSM (Maybe MediaTrackSupportedConstraints)
fromJSVal JSVal
v = (JSVal -> MediaTrackSupportedConstraints)
-> Maybe JSVal -> Maybe MediaTrackSupportedConstraints
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MediaTrackSupportedConstraints
MediaTrackSupportedConstraints (Maybe JSVal -> Maybe MediaTrackSupportedConstraints)
-> JSM (Maybe JSVal) -> JSM (Maybe MediaTrackSupportedConstraints)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MediaTrackSupportedConstraints
fromJSValUnchecked = MediaTrackSupportedConstraints
-> JSM MediaTrackSupportedConstraints
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaTrackSupportedConstraints
 -> JSM MediaTrackSupportedConstraints)
-> (JSVal -> MediaTrackSupportedConstraints)
-> JSVal
-> JSM MediaTrackSupportedConstraints
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MediaTrackSupportedConstraints
MediaTrackSupportedConstraints
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MediaTrackSupportedConstraints where
  makeObject :: MediaTrackSupportedConstraints -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MediaTrackSupportedConstraints -> JSVal)
-> MediaTrackSupportedConstraints
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaTrackSupportedConstraints -> JSVal
unMediaTrackSupportedConstraints

instance IsGObject MediaTrackSupportedConstraints where
  typeGType :: MediaTrackSupportedConstraints -> JSM GType
typeGType MediaTrackSupportedConstraints
_ = JSM GType
gTypeMediaTrackSupportedConstraints
  {-# INLINE typeGType #-}

noMediaTrackSupportedConstraints :: Maybe MediaTrackSupportedConstraints
noMediaTrackSupportedConstraints :: Maybe MediaTrackSupportedConstraints
noMediaTrackSupportedConstraints = Maybe MediaTrackSupportedConstraints
forall a. Maybe a
Nothing
{-# INLINE noMediaTrackSupportedConstraints #-}

gTypeMediaTrackSupportedConstraints :: JSM GType
gTypeMediaTrackSupportedConstraints :: JSM GType
gTypeMediaTrackSupportedConstraints = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MediaTrackSupportedConstraints"

-- | Functions for this inteface are in "JSDOM.MessageChannel".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MessageChannel Mozilla MessageChannel documentation>
newtype MessageChannel = MessageChannel { MessageChannel -> JSVal
unMessageChannel :: JSVal }

instance PToJSVal MessageChannel where
  pToJSVal :: MessageChannel -> JSVal
pToJSVal = MessageChannel -> JSVal
unMessageChannel
  {-# INLINE pToJSVal #-}

instance PFromJSVal MessageChannel where
  pFromJSVal :: JSVal -> MessageChannel
pFromJSVal = JSVal -> MessageChannel
MessageChannel
  {-# INLINE pFromJSVal #-}

instance ToJSVal MessageChannel where
  toJSVal :: MessageChannel -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MessageChannel -> JSVal) -> MessageChannel -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageChannel -> JSVal
unMessageChannel
  {-# INLINE toJSVal #-}

instance FromJSVal MessageChannel where
  fromJSVal :: JSVal -> JSM (Maybe MessageChannel)
fromJSVal JSVal
v = (JSVal -> MessageChannel) -> Maybe JSVal -> Maybe MessageChannel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MessageChannel
MessageChannel (Maybe JSVal -> Maybe MessageChannel)
-> JSM (Maybe JSVal) -> JSM (Maybe MessageChannel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MessageChannel
fromJSValUnchecked = MessageChannel -> JSM MessageChannel
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MessageChannel -> JSM MessageChannel)
-> (JSVal -> MessageChannel) -> JSVal -> JSM MessageChannel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MessageChannel
MessageChannel
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MessageChannel where
  makeObject :: MessageChannel -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MessageChannel -> JSVal) -> MessageChannel -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageChannel -> JSVal
unMessageChannel

instance IsGObject MessageChannel where
  typeGType :: MessageChannel -> JSM GType
typeGType MessageChannel
_ = JSM GType
gTypeMessageChannel
  {-# INLINE typeGType #-}

noMessageChannel :: Maybe MessageChannel
noMessageChannel :: Maybe MessageChannel
noMessageChannel = Maybe MessageChannel
forall a. Maybe a
Nothing
{-# INLINE noMessageChannel #-}

gTypeMessageChannel :: JSM GType
gTypeMessageChannel :: JSM GType
gTypeMessageChannel = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MessageChannel"

-- | Functions for this inteface are in "JSDOM.MessageEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MessageEvent Mozilla MessageEvent documentation>
newtype MessageEvent = MessageEvent { MessageEvent -> JSVal
unMessageEvent :: JSVal }

instance PToJSVal MessageEvent where
  pToJSVal :: MessageEvent -> JSVal
pToJSVal = MessageEvent -> JSVal
unMessageEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal MessageEvent where
  pFromJSVal :: JSVal -> MessageEvent
pFromJSVal = JSVal -> MessageEvent
MessageEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal MessageEvent where
  toJSVal :: MessageEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MessageEvent -> JSVal) -> MessageEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageEvent -> JSVal
unMessageEvent
  {-# INLINE toJSVal #-}

instance FromJSVal MessageEvent where
  fromJSVal :: JSVal -> JSM (Maybe MessageEvent)
fromJSVal JSVal
v = (JSVal -> MessageEvent) -> Maybe JSVal -> Maybe MessageEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MessageEvent
MessageEvent (Maybe JSVal -> Maybe MessageEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe MessageEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MessageEvent
fromJSValUnchecked = MessageEvent -> JSM MessageEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MessageEvent -> JSM MessageEvent)
-> (JSVal -> MessageEvent) -> JSVal -> JSM MessageEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MessageEvent
MessageEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MessageEvent where
  makeObject :: MessageEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MessageEvent -> JSVal) -> MessageEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageEvent -> JSVal
unMessageEvent

instance IsEvent MessageEvent
instance IsGObject MessageEvent where
  typeGType :: MessageEvent -> JSM GType
typeGType MessageEvent
_ = JSM GType
gTypeMessageEvent
  {-# INLINE typeGType #-}

noMessageEvent :: Maybe MessageEvent
noMessageEvent :: Maybe MessageEvent
noMessageEvent = Maybe MessageEvent
forall a. Maybe a
Nothing
{-# INLINE noMessageEvent #-}

gTypeMessageEvent :: JSM GType
gTypeMessageEvent :: JSM GType
gTypeMessageEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MessageEvent"

-- | Functions for this inteface are in "JSDOM.MessageEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MessageEventInit Mozilla MessageEventInit documentation>
newtype MessageEventInit = MessageEventInit { MessageEventInit -> JSVal
unMessageEventInit :: JSVal }

instance PToJSVal MessageEventInit where
  pToJSVal :: MessageEventInit -> JSVal
pToJSVal = MessageEventInit -> JSVal
unMessageEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal MessageEventInit where
  pFromJSVal :: JSVal -> MessageEventInit
pFromJSVal = JSVal -> MessageEventInit
MessageEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal MessageEventInit where
  toJSVal :: MessageEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MessageEventInit -> JSVal) -> MessageEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageEventInit -> JSVal
unMessageEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal MessageEventInit where
  fromJSVal :: JSVal -> JSM (Maybe MessageEventInit)
fromJSVal JSVal
v = (JSVal -> MessageEventInit)
-> Maybe JSVal -> Maybe MessageEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MessageEventInit
MessageEventInit (Maybe JSVal -> Maybe MessageEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe MessageEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MessageEventInit
fromJSValUnchecked = MessageEventInit -> JSM MessageEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MessageEventInit -> JSM MessageEventInit)
-> (JSVal -> MessageEventInit) -> JSVal -> JSM MessageEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MessageEventInit
MessageEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MessageEventInit where
  makeObject :: MessageEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MessageEventInit -> JSVal) -> MessageEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageEventInit -> JSVal
unMessageEventInit

instance IsEventInit MessageEventInit
instance IsGObject MessageEventInit where
  typeGType :: MessageEventInit -> JSM GType
typeGType MessageEventInit
_ = JSM GType
gTypeMessageEventInit
  {-# INLINE typeGType #-}

noMessageEventInit :: Maybe MessageEventInit
noMessageEventInit :: Maybe MessageEventInit
noMessageEventInit = Maybe MessageEventInit
forall a. Maybe a
Nothing
{-# INLINE noMessageEventInit #-}

gTypeMessageEventInit :: JSM GType
gTypeMessageEventInit :: JSM GType
gTypeMessageEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MessageEventInit"

-- | Functions for this inteface are in "JSDOM.MessagePort".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MessagePort Mozilla MessagePort documentation>
newtype MessagePort = MessagePort { MessagePort -> JSVal
unMessagePort :: JSVal }

instance PToJSVal MessagePort where
  pToJSVal :: MessagePort -> JSVal
pToJSVal = MessagePort -> JSVal
unMessagePort
  {-# INLINE pToJSVal #-}

instance PFromJSVal MessagePort where
  pFromJSVal :: JSVal -> MessagePort
pFromJSVal = JSVal -> MessagePort
MessagePort
  {-# INLINE pFromJSVal #-}

instance ToJSVal MessagePort where
  toJSVal :: MessagePort -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MessagePort -> JSVal) -> MessagePort -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessagePort -> JSVal
unMessagePort
  {-# INLINE toJSVal #-}

instance FromJSVal MessagePort where
  fromJSVal :: JSVal -> JSM (Maybe MessagePort)
fromJSVal JSVal
v = (JSVal -> MessagePort) -> Maybe JSVal -> Maybe MessagePort
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MessagePort
MessagePort (Maybe JSVal -> Maybe MessagePort)
-> JSM (Maybe JSVal) -> JSM (Maybe MessagePort)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MessagePort
fromJSValUnchecked = MessagePort -> JSM MessagePort
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MessagePort -> JSM MessagePort)
-> (JSVal -> MessagePort) -> JSVal -> JSM MessagePort
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MessagePort
MessagePort
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MessagePort where
  makeObject :: MessagePort -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MessagePort -> JSVal) -> MessagePort -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessagePort -> JSVal
unMessagePort

instance IsEventTarget MessagePort
instance IsGObject MessagePort where
  typeGType :: MessagePort -> JSM GType
typeGType MessagePort
_ = JSM GType
gTypeMessagePort
  {-# INLINE typeGType #-}

noMessagePort :: Maybe MessagePort
noMessagePort :: Maybe MessagePort
noMessagePort = Maybe MessagePort
forall a. Maybe a
Nothing
{-# INLINE noMessagePort #-}

gTypeMessagePort :: JSM GType
gTypeMessagePort :: JSM GType
gTypeMessagePort = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MessagePort"

-- | Functions for this inteface are in "JSDOM.MimeType".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MimeType Mozilla MimeType documentation>
newtype MimeType = MimeType { MimeType -> JSVal
unMimeType :: JSVal }

instance PToJSVal MimeType where
  pToJSVal :: MimeType -> JSVal
pToJSVal = MimeType -> JSVal
unMimeType
  {-# INLINE pToJSVal #-}

instance PFromJSVal MimeType where
  pFromJSVal :: JSVal -> MimeType
pFromJSVal = JSVal -> MimeType
MimeType
  {-# INLINE pFromJSVal #-}

instance ToJSVal MimeType where
  toJSVal :: MimeType -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MimeType -> JSVal) -> MimeType -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MimeType -> JSVal
unMimeType
  {-# INLINE toJSVal #-}

instance FromJSVal MimeType where
  fromJSVal :: JSVal -> JSM (Maybe MimeType)
fromJSVal JSVal
v = (JSVal -> MimeType) -> Maybe JSVal -> Maybe MimeType
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MimeType
MimeType (Maybe JSVal -> Maybe MimeType)
-> JSM (Maybe JSVal) -> JSM (Maybe MimeType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MimeType
fromJSValUnchecked = MimeType -> JSM MimeType
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MimeType -> JSM MimeType)
-> (JSVal -> MimeType) -> JSVal -> JSM MimeType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MimeType
MimeType
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MimeType where
  makeObject :: MimeType -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MimeType -> JSVal) -> MimeType -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MimeType -> JSVal
unMimeType

instance IsGObject MimeType where
  typeGType :: MimeType -> JSM GType
typeGType MimeType
_ = JSM GType
gTypeMimeType
  {-# INLINE typeGType #-}

noMimeType :: Maybe MimeType
noMimeType :: Maybe MimeType
noMimeType = Maybe MimeType
forall a. Maybe a
Nothing
{-# INLINE noMimeType #-}

gTypeMimeType :: JSM GType
gTypeMimeType :: JSM GType
gTypeMimeType = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MimeType"

-- | Functions for this inteface are in "JSDOM.MimeTypeArray".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MimeTypeArray Mozilla MimeTypeArray documentation>
newtype MimeTypeArray = MimeTypeArray { MimeTypeArray -> JSVal
unMimeTypeArray :: JSVal }

instance PToJSVal MimeTypeArray where
  pToJSVal :: MimeTypeArray -> JSVal
pToJSVal = MimeTypeArray -> JSVal
unMimeTypeArray
  {-# INLINE pToJSVal #-}

instance PFromJSVal MimeTypeArray where
  pFromJSVal :: JSVal -> MimeTypeArray
pFromJSVal = JSVal -> MimeTypeArray
MimeTypeArray
  {-# INLINE pFromJSVal #-}

instance ToJSVal MimeTypeArray where
  toJSVal :: MimeTypeArray -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MimeTypeArray -> JSVal) -> MimeTypeArray -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MimeTypeArray -> JSVal
unMimeTypeArray
  {-# INLINE toJSVal #-}

instance FromJSVal MimeTypeArray where
  fromJSVal :: JSVal -> JSM (Maybe MimeTypeArray)
fromJSVal JSVal
v = (JSVal -> MimeTypeArray) -> Maybe JSVal -> Maybe MimeTypeArray
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MimeTypeArray
MimeTypeArray (Maybe JSVal -> Maybe MimeTypeArray)
-> JSM (Maybe JSVal) -> JSM (Maybe MimeTypeArray)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MimeTypeArray
fromJSValUnchecked = MimeTypeArray -> JSM MimeTypeArray
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MimeTypeArray -> JSM MimeTypeArray)
-> (JSVal -> MimeTypeArray) -> JSVal -> JSM MimeTypeArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MimeTypeArray
MimeTypeArray
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MimeTypeArray where
  makeObject :: MimeTypeArray -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MimeTypeArray -> JSVal) -> MimeTypeArray -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MimeTypeArray -> JSVal
unMimeTypeArray

instance IsGObject MimeTypeArray where
  typeGType :: MimeTypeArray -> JSM GType
typeGType MimeTypeArray
_ = JSM GType
gTypeMimeTypeArray
  {-# INLINE typeGType #-}

noMimeTypeArray :: Maybe MimeTypeArray
noMimeTypeArray :: Maybe MimeTypeArray
noMimeTypeArray = Maybe MimeTypeArray
forall a. Maybe a
Nothing
{-# INLINE noMimeTypeArray #-}

gTypeMimeTypeArray :: JSM GType
gTypeMimeTypeArray :: JSM GType
gTypeMimeTypeArray = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MimeTypeArray"

-- | Functions for this inteface are in "JSDOM.MouseEvent".
-- Base interface functions are in:
--
--     * "JSDOM.UIEvent"
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MouseEvent Mozilla MouseEvent documentation>
newtype MouseEvent = MouseEvent { MouseEvent -> JSVal
unMouseEvent :: JSVal }

instance PToJSVal MouseEvent where
  pToJSVal :: MouseEvent -> JSVal
pToJSVal = MouseEvent -> JSVal
unMouseEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal MouseEvent where
  pFromJSVal :: JSVal -> MouseEvent
pFromJSVal = JSVal -> MouseEvent
MouseEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal MouseEvent where
  toJSVal :: MouseEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MouseEvent -> JSVal) -> MouseEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MouseEvent -> JSVal
unMouseEvent
  {-# INLINE toJSVal #-}

instance FromJSVal MouseEvent where
  fromJSVal :: JSVal -> JSM (Maybe MouseEvent)
fromJSVal JSVal
v = (JSVal -> MouseEvent) -> Maybe JSVal -> Maybe MouseEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MouseEvent
MouseEvent (Maybe JSVal -> Maybe MouseEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe MouseEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MouseEvent
fromJSValUnchecked = MouseEvent -> JSM MouseEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MouseEvent -> JSM MouseEvent)
-> (JSVal -> MouseEvent) -> JSVal -> JSM MouseEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MouseEvent
MouseEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MouseEvent where
  makeObject :: MouseEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MouseEvent -> JSVal) -> MouseEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MouseEvent -> JSVal
unMouseEvent

class (IsUIEvent o, IsEvent o, IsGObject o) => IsMouseEvent o
toMouseEvent :: IsMouseEvent o => o -> MouseEvent
toMouseEvent :: forall o. IsMouseEvent o => o -> MouseEvent
toMouseEvent = JSVal -> MouseEvent
MouseEvent (JSVal -> MouseEvent) -> (o -> JSVal) -> o -> MouseEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsMouseEvent MouseEvent
instance IsUIEvent MouseEvent
instance IsEvent MouseEvent
instance IsGObject MouseEvent where
  typeGType :: MouseEvent -> JSM GType
typeGType MouseEvent
_ = JSM GType
gTypeMouseEvent
  {-# INLINE typeGType #-}

noMouseEvent :: Maybe MouseEvent
noMouseEvent :: Maybe MouseEvent
noMouseEvent = Maybe MouseEvent
forall a. Maybe a
Nothing
{-# INLINE noMouseEvent #-}

gTypeMouseEvent :: JSM GType
gTypeMouseEvent :: JSM GType
gTypeMouseEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MouseEvent"

-- | Functions for this inteface are in "JSDOM.MouseEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventModifierInit"
--     * "JSDOM.UIEventInit"
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MouseEventInit Mozilla MouseEventInit documentation>
newtype MouseEventInit = MouseEventInit { MouseEventInit -> JSVal
unMouseEventInit :: JSVal }

instance PToJSVal MouseEventInit where
  pToJSVal :: MouseEventInit -> JSVal
pToJSVal = MouseEventInit -> JSVal
unMouseEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal MouseEventInit where
  pFromJSVal :: JSVal -> MouseEventInit
pFromJSVal = JSVal -> MouseEventInit
MouseEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal MouseEventInit where
  toJSVal :: MouseEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MouseEventInit -> JSVal) -> MouseEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MouseEventInit -> JSVal
unMouseEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal MouseEventInit where
  fromJSVal :: JSVal -> JSM (Maybe MouseEventInit)
fromJSVal JSVal
v = (JSVal -> MouseEventInit) -> Maybe JSVal -> Maybe MouseEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MouseEventInit
MouseEventInit (Maybe JSVal -> Maybe MouseEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe MouseEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MouseEventInit
fromJSValUnchecked = MouseEventInit -> JSM MouseEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MouseEventInit -> JSM MouseEventInit)
-> (JSVal -> MouseEventInit) -> JSVal -> JSM MouseEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MouseEventInit
MouseEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MouseEventInit where
  makeObject :: MouseEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MouseEventInit -> JSVal) -> MouseEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MouseEventInit -> JSVal
unMouseEventInit

class (IsEventModifierInit o, IsUIEventInit o, IsEventInit o, IsGObject o) => IsMouseEventInit o
toMouseEventInit :: IsMouseEventInit o => o -> MouseEventInit
toMouseEventInit :: forall o. IsMouseEventInit o => o -> MouseEventInit
toMouseEventInit = JSVal -> MouseEventInit
MouseEventInit (JSVal -> MouseEventInit) -> (o -> JSVal) -> o -> MouseEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsMouseEventInit MouseEventInit
instance IsEventModifierInit MouseEventInit
instance IsUIEventInit MouseEventInit
instance IsEventInit MouseEventInit
instance IsGObject MouseEventInit where
  typeGType :: MouseEventInit -> JSM GType
typeGType MouseEventInit
_ = JSM GType
gTypeMouseEventInit
  {-# INLINE typeGType #-}

noMouseEventInit :: Maybe MouseEventInit
noMouseEventInit :: Maybe MouseEventInit
noMouseEventInit = Maybe MouseEventInit
forall a. Maybe a
Nothing
{-# INLINE noMouseEventInit #-}

gTypeMouseEventInit :: JSM GType
gTypeMouseEventInit :: JSM GType
gTypeMouseEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MouseEventInit"

-- | Functions for this inteface are in "JSDOM.MutationEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MutationEvent Mozilla MutationEvent documentation>
newtype MutationEvent = MutationEvent { MutationEvent -> JSVal
unMutationEvent :: JSVal }

instance PToJSVal MutationEvent where
  pToJSVal :: MutationEvent -> JSVal
pToJSVal = MutationEvent -> JSVal
unMutationEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal MutationEvent where
  pFromJSVal :: JSVal -> MutationEvent
pFromJSVal = JSVal -> MutationEvent
MutationEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal MutationEvent where
  toJSVal :: MutationEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MutationEvent -> JSVal) -> MutationEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutationEvent -> JSVal
unMutationEvent
  {-# INLINE toJSVal #-}

instance FromJSVal MutationEvent where
  fromJSVal :: JSVal -> JSM (Maybe MutationEvent)
fromJSVal JSVal
v = (JSVal -> MutationEvent) -> Maybe JSVal -> Maybe MutationEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MutationEvent
MutationEvent (Maybe JSVal -> Maybe MutationEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe MutationEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MutationEvent
fromJSValUnchecked = MutationEvent -> JSM MutationEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MutationEvent -> JSM MutationEvent)
-> (JSVal -> MutationEvent) -> JSVal -> JSM MutationEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MutationEvent
MutationEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MutationEvent where
  makeObject :: MutationEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MutationEvent -> JSVal) -> MutationEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutationEvent -> JSVal
unMutationEvent

instance IsEvent MutationEvent
instance IsGObject MutationEvent where
  typeGType :: MutationEvent -> JSM GType
typeGType MutationEvent
_ = JSM GType
gTypeMutationEvent
  {-# INLINE typeGType #-}

noMutationEvent :: Maybe MutationEvent
noMutationEvent :: Maybe MutationEvent
noMutationEvent = Maybe MutationEvent
forall a. Maybe a
Nothing
{-# INLINE noMutationEvent #-}

gTypeMutationEvent :: JSM GType
gTypeMutationEvent :: JSM GType
gTypeMutationEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MutationEvent"

-- | Functions for this inteface are in "JSDOM.MutationObserver".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MutationObserver Mozilla MutationObserver documentation>
newtype MutationObserver = MutationObserver { MutationObserver -> JSVal
unMutationObserver :: JSVal }

instance PToJSVal MutationObserver where
  pToJSVal :: MutationObserver -> JSVal
pToJSVal = MutationObserver -> JSVal
unMutationObserver
  {-# INLINE pToJSVal #-}

instance PFromJSVal MutationObserver where
  pFromJSVal :: JSVal -> MutationObserver
pFromJSVal = JSVal -> MutationObserver
MutationObserver
  {-# INLINE pFromJSVal #-}

instance ToJSVal MutationObserver where
  toJSVal :: MutationObserver -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MutationObserver -> JSVal) -> MutationObserver -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutationObserver -> JSVal
unMutationObserver
  {-# INLINE toJSVal #-}

instance FromJSVal MutationObserver where
  fromJSVal :: JSVal -> JSM (Maybe MutationObserver)
fromJSVal JSVal
v = (JSVal -> MutationObserver)
-> Maybe JSVal -> Maybe MutationObserver
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MutationObserver
MutationObserver (Maybe JSVal -> Maybe MutationObserver)
-> JSM (Maybe JSVal) -> JSM (Maybe MutationObserver)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MutationObserver
fromJSValUnchecked = MutationObserver -> JSM MutationObserver
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MutationObserver -> JSM MutationObserver)
-> (JSVal -> MutationObserver) -> JSVal -> JSM MutationObserver
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MutationObserver
MutationObserver
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MutationObserver where
  makeObject :: MutationObserver -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MutationObserver -> JSVal) -> MutationObserver -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutationObserver -> JSVal
unMutationObserver

instance IsGObject MutationObserver where
  typeGType :: MutationObserver -> JSM GType
typeGType MutationObserver
_ = JSM GType
gTypeMutationObserver
  {-# INLINE typeGType #-}

noMutationObserver :: Maybe MutationObserver
noMutationObserver :: Maybe MutationObserver
noMutationObserver = Maybe MutationObserver
forall a. Maybe a
Nothing
{-# INLINE noMutationObserver #-}

gTypeMutationObserver :: JSM GType
gTypeMutationObserver :: JSM GType
gTypeMutationObserver = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MutationObserver"

-- | Functions for this inteface are in "JSDOM.MutationObserverInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MutationObserverInit Mozilla MutationObserverInit documentation>
newtype MutationObserverInit = MutationObserverInit { MutationObserverInit -> JSVal
unMutationObserverInit :: JSVal }

instance PToJSVal MutationObserverInit where
  pToJSVal :: MutationObserverInit -> JSVal
pToJSVal = MutationObserverInit -> JSVal
unMutationObserverInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal MutationObserverInit where
  pFromJSVal :: JSVal -> MutationObserverInit
pFromJSVal = JSVal -> MutationObserverInit
MutationObserverInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal MutationObserverInit where
  toJSVal :: MutationObserverInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MutationObserverInit -> JSVal)
-> MutationObserverInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutationObserverInit -> JSVal
unMutationObserverInit
  {-# INLINE toJSVal #-}

instance FromJSVal MutationObserverInit where
  fromJSVal :: JSVal -> JSM (Maybe MutationObserverInit)
fromJSVal JSVal
v = (JSVal -> MutationObserverInit)
-> Maybe JSVal -> Maybe MutationObserverInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MutationObserverInit
MutationObserverInit (Maybe JSVal -> Maybe MutationObserverInit)
-> JSM (Maybe JSVal) -> JSM (Maybe MutationObserverInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MutationObserverInit
fromJSValUnchecked = MutationObserverInit -> JSM MutationObserverInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MutationObserverInit -> JSM MutationObserverInit)
-> (JSVal -> MutationObserverInit)
-> JSVal
-> JSM MutationObserverInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MutationObserverInit
MutationObserverInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MutationObserverInit where
  makeObject :: MutationObserverInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MutationObserverInit -> JSVal)
-> MutationObserverInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutationObserverInit -> JSVal
unMutationObserverInit

instance IsGObject MutationObserverInit where
  typeGType :: MutationObserverInit -> JSM GType
typeGType MutationObserverInit
_ = JSM GType
gTypeMutationObserverInit
  {-# INLINE typeGType #-}

noMutationObserverInit :: Maybe MutationObserverInit
noMutationObserverInit :: Maybe MutationObserverInit
noMutationObserverInit = Maybe MutationObserverInit
forall a. Maybe a
Nothing
{-# INLINE noMutationObserverInit #-}

gTypeMutationObserverInit :: JSM GType
gTypeMutationObserverInit :: JSM GType
gTypeMutationObserverInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MutationObserverInit"

-- | Functions for this inteface are in "JSDOM.MutationRecord".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/MutationRecord Mozilla MutationRecord documentation>
newtype MutationRecord = MutationRecord { MutationRecord -> JSVal
unMutationRecord :: JSVal }

instance PToJSVal MutationRecord where
  pToJSVal :: MutationRecord -> JSVal
pToJSVal = MutationRecord -> JSVal
unMutationRecord
  {-# INLINE pToJSVal #-}

instance PFromJSVal MutationRecord where
  pFromJSVal :: JSVal -> MutationRecord
pFromJSVal = JSVal -> MutationRecord
MutationRecord
  {-# INLINE pFromJSVal #-}

instance ToJSVal MutationRecord where
  toJSVal :: MutationRecord -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (MutationRecord -> JSVal) -> MutationRecord -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutationRecord -> JSVal
unMutationRecord
  {-# INLINE toJSVal #-}

instance FromJSVal MutationRecord where
  fromJSVal :: JSVal -> JSM (Maybe MutationRecord)
fromJSVal JSVal
v = (JSVal -> MutationRecord) -> Maybe JSVal -> Maybe MutationRecord
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> MutationRecord
MutationRecord (Maybe JSVal -> Maybe MutationRecord)
-> JSM (Maybe JSVal) -> JSM (Maybe MutationRecord)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM MutationRecord
fromJSValUnchecked = MutationRecord -> JSM MutationRecord
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (MutationRecord -> JSM MutationRecord)
-> (JSVal -> MutationRecord) -> JSVal -> JSM MutationRecord
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> MutationRecord
MutationRecord
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject MutationRecord where
  makeObject :: MutationRecord -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (MutationRecord -> JSVal) -> MutationRecord -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutationRecord -> JSVal
unMutationRecord

instance IsGObject MutationRecord where
  typeGType :: MutationRecord -> JSM GType
typeGType MutationRecord
_ = JSM GType
gTypeMutationRecord
  {-# INLINE typeGType #-}

noMutationRecord :: Maybe MutationRecord
noMutationRecord :: Maybe MutationRecord
noMutationRecord = Maybe MutationRecord
forall a. Maybe a
Nothing
{-# INLINE noMutationRecord #-}

gTypeMutationRecord :: JSM GType
gTypeMutationRecord :: JSM GType
gTypeMutationRecord = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"MutationRecord"

-- | Functions for this inteface are in "JSDOM.NamedNodeMap".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/NamedNodeMap Mozilla NamedNodeMap documentation>
newtype NamedNodeMap = NamedNodeMap { NamedNodeMap -> JSVal
unNamedNodeMap :: JSVal }

instance PToJSVal NamedNodeMap where
  pToJSVal :: NamedNodeMap -> JSVal
pToJSVal = NamedNodeMap -> JSVal
unNamedNodeMap
  {-# INLINE pToJSVal #-}

instance PFromJSVal NamedNodeMap where
  pFromJSVal :: JSVal -> NamedNodeMap
pFromJSVal = JSVal -> NamedNodeMap
NamedNodeMap
  {-# INLINE pFromJSVal #-}

instance ToJSVal NamedNodeMap where
  toJSVal :: NamedNodeMap -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NamedNodeMap -> JSVal) -> NamedNodeMap -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NamedNodeMap -> JSVal
unNamedNodeMap
  {-# INLINE toJSVal #-}

instance FromJSVal NamedNodeMap where
  fromJSVal :: JSVal -> JSM (Maybe NamedNodeMap)
fromJSVal JSVal
v = (JSVal -> NamedNodeMap) -> Maybe JSVal -> Maybe NamedNodeMap
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NamedNodeMap
NamedNodeMap (Maybe JSVal -> Maybe NamedNodeMap)
-> JSM (Maybe JSVal) -> JSM (Maybe NamedNodeMap)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NamedNodeMap
fromJSValUnchecked = NamedNodeMap -> JSM NamedNodeMap
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NamedNodeMap -> JSM NamedNodeMap)
-> (JSVal -> NamedNodeMap) -> JSVal -> JSM NamedNodeMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NamedNodeMap
NamedNodeMap
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NamedNodeMap where
  makeObject :: NamedNodeMap -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NamedNodeMap -> JSVal) -> NamedNodeMap -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NamedNodeMap -> JSVal
unNamedNodeMap

instance IsGObject NamedNodeMap where
  typeGType :: NamedNodeMap -> JSM GType
typeGType NamedNodeMap
_ = JSM GType
gTypeNamedNodeMap
  {-# INLINE typeGType #-}

noNamedNodeMap :: Maybe NamedNodeMap
noNamedNodeMap :: Maybe NamedNodeMap
noNamedNodeMap = Maybe NamedNodeMap
forall a. Maybe a
Nothing
{-# INLINE noNamedNodeMap #-}

gTypeNamedNodeMap :: JSM GType
gTypeNamedNodeMap :: JSM GType
gTypeNamedNodeMap = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"NamedNodeMap"

-- | Functions for this inteface are in "JSDOM.Navigator".
-- Base interface functions are in:
--
--     * "JSDOM.NavigatorOnLine"
--     * "JSDOM.NavigatorLanguage"
--     * "JSDOM.NavigatorID"
--     * "JSDOM.NavigatorConcurrentHardware"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Navigator Mozilla Navigator documentation>
newtype Navigator = Navigator { Navigator -> JSVal
unNavigator :: JSVal }

instance PToJSVal Navigator where
  pToJSVal :: Navigator -> JSVal
pToJSVal = Navigator -> JSVal
unNavigator
  {-# INLINE pToJSVal #-}

instance PFromJSVal Navigator where
  pFromJSVal :: JSVal -> Navigator
pFromJSVal = JSVal -> Navigator
Navigator
  {-# INLINE pFromJSVal #-}

instance ToJSVal Navigator where
  toJSVal :: Navigator -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Navigator -> JSVal) -> Navigator -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Navigator -> JSVal
unNavigator
  {-# INLINE toJSVal #-}

instance FromJSVal Navigator where
  fromJSVal :: JSVal -> JSM (Maybe Navigator)
fromJSVal JSVal
v = (JSVal -> Navigator) -> Maybe JSVal -> Maybe Navigator
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Navigator
Navigator (Maybe JSVal -> Maybe Navigator)
-> JSM (Maybe JSVal) -> JSM (Maybe Navigator)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Navigator
fromJSValUnchecked = Navigator -> JSM Navigator
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Navigator -> JSM Navigator)
-> (JSVal -> Navigator) -> JSVal -> JSM Navigator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Navigator
Navigator
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Navigator where
  makeObject :: Navigator -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Navigator -> JSVal) -> Navigator -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Navigator -> JSVal
unNavigator

instance IsNavigatorOnLine Navigator
instance IsNavigatorLanguage Navigator
instance IsNavigatorID Navigator
instance IsNavigatorConcurrentHardware Navigator
instance IsGObject Navigator where
  typeGType :: Navigator -> JSM GType
typeGType Navigator
_ = JSM GType
gTypeNavigator
  {-# INLINE typeGType #-}

noNavigator :: Maybe Navigator
noNavigator :: Maybe Navigator
noNavigator = Maybe Navigator
forall a. Maybe a
Nothing
{-# INLINE noNavigator #-}

gTypeNavigator :: JSM GType
gTypeNavigator :: JSM GType
gTypeNavigator = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Navigator"

-- | Functions for this inteface are in "JSDOM.NavigatorConcurrentHardware".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/NavigatorConcurrentHardware Mozilla NavigatorConcurrentHardware documentation>
newtype NavigatorConcurrentHardware = NavigatorConcurrentHardware { NavigatorConcurrentHardware -> JSVal
unNavigatorConcurrentHardware :: JSVal }

instance PToJSVal NavigatorConcurrentHardware where
  pToJSVal :: NavigatorConcurrentHardware -> JSVal
pToJSVal = NavigatorConcurrentHardware -> JSVal
unNavigatorConcurrentHardware
  {-# INLINE pToJSVal #-}

instance PFromJSVal NavigatorConcurrentHardware where
  pFromJSVal :: JSVal -> NavigatorConcurrentHardware
pFromJSVal = JSVal -> NavigatorConcurrentHardware
NavigatorConcurrentHardware
  {-# INLINE pFromJSVal #-}

instance ToJSVal NavigatorConcurrentHardware where
  toJSVal :: NavigatorConcurrentHardware -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NavigatorConcurrentHardware -> JSVal)
-> NavigatorConcurrentHardware
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NavigatorConcurrentHardware -> JSVal
unNavigatorConcurrentHardware
  {-# INLINE toJSVal #-}

instance FromJSVal NavigatorConcurrentHardware where
  fromJSVal :: JSVal -> JSM (Maybe NavigatorConcurrentHardware)
fromJSVal JSVal
v = (JSVal -> NavigatorConcurrentHardware)
-> Maybe JSVal -> Maybe NavigatorConcurrentHardware
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NavigatorConcurrentHardware
NavigatorConcurrentHardware (Maybe JSVal -> Maybe NavigatorConcurrentHardware)
-> JSM (Maybe JSVal) -> JSM (Maybe NavigatorConcurrentHardware)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NavigatorConcurrentHardware
fromJSValUnchecked = NavigatorConcurrentHardware -> JSM NavigatorConcurrentHardware
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NavigatorConcurrentHardware -> JSM NavigatorConcurrentHardware)
-> (JSVal -> NavigatorConcurrentHardware)
-> JSVal
-> JSM NavigatorConcurrentHardware
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NavigatorConcurrentHardware
NavigatorConcurrentHardware
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NavigatorConcurrentHardware where
  makeObject :: NavigatorConcurrentHardware -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NavigatorConcurrentHardware -> JSVal)
-> NavigatorConcurrentHardware
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NavigatorConcurrentHardware -> JSVal
unNavigatorConcurrentHardware

class (IsGObject o) => IsNavigatorConcurrentHardware o
toNavigatorConcurrentHardware :: IsNavigatorConcurrentHardware o => o -> NavigatorConcurrentHardware
toNavigatorConcurrentHardware :: forall o.
IsNavigatorConcurrentHardware o =>
o -> NavigatorConcurrentHardware
toNavigatorConcurrentHardware = JSVal -> NavigatorConcurrentHardware
NavigatorConcurrentHardware (JSVal -> NavigatorConcurrentHardware)
-> (o -> JSVal) -> o -> NavigatorConcurrentHardware
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsNavigatorConcurrentHardware NavigatorConcurrentHardware
instance IsGObject NavigatorConcurrentHardware where
  typeGType :: NavigatorConcurrentHardware -> JSM GType
typeGType NavigatorConcurrentHardware
_ = JSM GType
gTypeNavigatorConcurrentHardware
  {-# INLINE typeGType #-}

noNavigatorConcurrentHardware :: Maybe NavigatorConcurrentHardware
noNavigatorConcurrentHardware :: Maybe NavigatorConcurrentHardware
noNavigatorConcurrentHardware = Maybe NavigatorConcurrentHardware
forall a. Maybe a
Nothing
{-# INLINE noNavigatorConcurrentHardware #-}

gTypeNavigatorConcurrentHardware :: JSM GType
gTypeNavigatorConcurrentHardware :: JSM GType
gTypeNavigatorConcurrentHardware = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"NavigatorConcurrentHardware"

-- | Functions for this inteface are in "JSDOM.NavigatorID".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/NavigatorID Mozilla NavigatorID documentation>
newtype NavigatorID = NavigatorID { NavigatorID -> JSVal
unNavigatorID :: JSVal }

instance PToJSVal NavigatorID where
  pToJSVal :: NavigatorID -> JSVal
pToJSVal = NavigatorID -> JSVal
unNavigatorID
  {-# INLINE pToJSVal #-}

instance PFromJSVal NavigatorID where
  pFromJSVal :: JSVal -> NavigatorID
pFromJSVal = JSVal -> NavigatorID
NavigatorID
  {-# INLINE pFromJSVal #-}

instance ToJSVal NavigatorID where
  toJSVal :: NavigatorID -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NavigatorID -> JSVal) -> NavigatorID -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NavigatorID -> JSVal
unNavigatorID
  {-# INLINE toJSVal #-}

instance FromJSVal NavigatorID where
  fromJSVal :: JSVal -> JSM (Maybe NavigatorID)
fromJSVal JSVal
v = (JSVal -> NavigatorID) -> Maybe JSVal -> Maybe NavigatorID
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NavigatorID
NavigatorID (Maybe JSVal -> Maybe NavigatorID)
-> JSM (Maybe JSVal) -> JSM (Maybe NavigatorID)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NavigatorID
fromJSValUnchecked = NavigatorID -> JSM NavigatorID
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NavigatorID -> JSM NavigatorID)
-> (JSVal -> NavigatorID) -> JSVal -> JSM NavigatorID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NavigatorID
NavigatorID
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NavigatorID where
  makeObject :: NavigatorID -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NavigatorID -> JSVal) -> NavigatorID -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NavigatorID -> JSVal
unNavigatorID

class (IsGObject o) => IsNavigatorID o
toNavigatorID :: IsNavigatorID o => o -> NavigatorID
toNavigatorID :: forall o. IsNavigatorID o => o -> NavigatorID
toNavigatorID = JSVal -> NavigatorID
NavigatorID (JSVal -> NavigatorID) -> (o -> JSVal) -> o -> NavigatorID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsNavigatorID NavigatorID
instance IsGObject NavigatorID where
  typeGType :: NavigatorID -> JSM GType
typeGType NavigatorID
_ = JSM GType
gTypeNavigatorID
  {-# INLINE typeGType #-}

noNavigatorID :: Maybe NavigatorID
noNavigatorID :: Maybe NavigatorID
noNavigatorID = Maybe NavigatorID
forall a. Maybe a
Nothing
{-# INLINE noNavigatorID #-}

gTypeNavigatorID :: JSM GType
gTypeNavigatorID :: JSM GType
gTypeNavigatorID = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"NavigatorID"

-- | Functions for this inteface are in "JSDOM.NavigatorLanguage".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/NavigatorLanguage Mozilla NavigatorLanguage documentation>
newtype NavigatorLanguage = NavigatorLanguage { NavigatorLanguage -> JSVal
unNavigatorLanguage :: JSVal }

instance PToJSVal NavigatorLanguage where
  pToJSVal :: NavigatorLanguage -> JSVal
pToJSVal = NavigatorLanguage -> JSVal
unNavigatorLanguage
  {-# INLINE pToJSVal #-}

instance PFromJSVal NavigatorLanguage where
  pFromJSVal :: JSVal -> NavigatorLanguage
pFromJSVal = JSVal -> NavigatorLanguage
NavigatorLanguage
  {-# INLINE pFromJSVal #-}

instance ToJSVal NavigatorLanguage where
  toJSVal :: NavigatorLanguage -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NavigatorLanguage -> JSVal) -> NavigatorLanguage -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NavigatorLanguage -> JSVal
unNavigatorLanguage
  {-# INLINE toJSVal #-}

instance FromJSVal NavigatorLanguage where
  fromJSVal :: JSVal -> JSM (Maybe NavigatorLanguage)
fromJSVal JSVal
v = (JSVal -> NavigatorLanguage)
-> Maybe JSVal -> Maybe NavigatorLanguage
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NavigatorLanguage
NavigatorLanguage (Maybe JSVal -> Maybe NavigatorLanguage)
-> JSM (Maybe JSVal) -> JSM (Maybe NavigatorLanguage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NavigatorLanguage
fromJSValUnchecked = NavigatorLanguage -> JSM NavigatorLanguage
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NavigatorLanguage -> JSM NavigatorLanguage)
-> (JSVal -> NavigatorLanguage) -> JSVal -> JSM NavigatorLanguage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NavigatorLanguage
NavigatorLanguage
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NavigatorLanguage where
  makeObject :: NavigatorLanguage -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NavigatorLanguage -> JSVal) -> NavigatorLanguage -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NavigatorLanguage -> JSVal
unNavigatorLanguage

class (IsGObject o) => IsNavigatorLanguage o
toNavigatorLanguage :: IsNavigatorLanguage o => o -> NavigatorLanguage
toNavigatorLanguage :: forall o. IsNavigatorLanguage o => o -> NavigatorLanguage
toNavigatorLanguage = JSVal -> NavigatorLanguage
NavigatorLanguage (JSVal -> NavigatorLanguage)
-> (o -> JSVal) -> o -> NavigatorLanguage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsNavigatorLanguage NavigatorLanguage
instance IsGObject NavigatorLanguage where
  typeGType :: NavigatorLanguage -> JSM GType
typeGType NavigatorLanguage
_ = JSM GType
gTypeNavigatorLanguage
  {-# INLINE typeGType #-}

noNavigatorLanguage :: Maybe NavigatorLanguage
noNavigatorLanguage :: Maybe NavigatorLanguage
noNavigatorLanguage = Maybe NavigatorLanguage
forall a. Maybe a
Nothing
{-# INLINE noNavigatorLanguage #-}

gTypeNavigatorLanguage :: JSM GType
gTypeNavigatorLanguage :: JSM GType
gTypeNavigatorLanguage = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"NavigatorLanguage"

-- | Functions for this inteface are in "JSDOM.NavigatorOnLine".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/NavigatorOnLine Mozilla NavigatorOnLine documentation>
newtype NavigatorOnLine = NavigatorOnLine { NavigatorOnLine -> JSVal
unNavigatorOnLine :: JSVal }

instance PToJSVal NavigatorOnLine where
  pToJSVal :: NavigatorOnLine -> JSVal
pToJSVal = NavigatorOnLine -> JSVal
unNavigatorOnLine
  {-# INLINE pToJSVal #-}

instance PFromJSVal NavigatorOnLine where
  pFromJSVal :: JSVal -> NavigatorOnLine
pFromJSVal = JSVal -> NavigatorOnLine
NavigatorOnLine
  {-# INLINE pFromJSVal #-}

instance ToJSVal NavigatorOnLine where
  toJSVal :: NavigatorOnLine -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NavigatorOnLine -> JSVal) -> NavigatorOnLine -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NavigatorOnLine -> JSVal
unNavigatorOnLine
  {-# INLINE toJSVal #-}

instance FromJSVal NavigatorOnLine where
  fromJSVal :: JSVal -> JSM (Maybe NavigatorOnLine)
fromJSVal JSVal
v = (JSVal -> NavigatorOnLine) -> Maybe JSVal -> Maybe NavigatorOnLine
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NavigatorOnLine
NavigatorOnLine (Maybe JSVal -> Maybe NavigatorOnLine)
-> JSM (Maybe JSVal) -> JSM (Maybe NavigatorOnLine)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NavigatorOnLine
fromJSValUnchecked = NavigatorOnLine -> JSM NavigatorOnLine
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NavigatorOnLine -> JSM NavigatorOnLine)
-> (JSVal -> NavigatorOnLine) -> JSVal -> JSM NavigatorOnLine
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NavigatorOnLine
NavigatorOnLine
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NavigatorOnLine where
  makeObject :: NavigatorOnLine -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NavigatorOnLine -> JSVal) -> NavigatorOnLine -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NavigatorOnLine -> JSVal
unNavigatorOnLine

class (IsGObject o) => IsNavigatorOnLine o
toNavigatorOnLine :: IsNavigatorOnLine o => o -> NavigatorOnLine
toNavigatorOnLine :: forall o. IsNavigatorOnLine o => o -> NavigatorOnLine
toNavigatorOnLine = JSVal -> NavigatorOnLine
NavigatorOnLine (JSVal -> NavigatorOnLine) -> (o -> JSVal) -> o -> NavigatorOnLine
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsNavigatorOnLine NavigatorOnLine
instance IsGObject NavigatorOnLine where
  typeGType :: NavigatorOnLine -> JSM GType
typeGType NavigatorOnLine
_ = JSM GType
gTypeNavigatorOnLine
  {-# INLINE typeGType #-}

noNavigatorOnLine :: Maybe NavigatorOnLine
noNavigatorOnLine :: Maybe NavigatorOnLine
noNavigatorOnLine = Maybe NavigatorOnLine
forall a. Maybe a
Nothing
{-# INLINE noNavigatorOnLine #-}

gTypeNavigatorOnLine :: JSM GType
gTypeNavigatorOnLine :: JSM GType
gTypeNavigatorOnLine = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"NavigatorOnLine"

-- | Functions for this inteface are in "JSDOM.NavigatorUserMediaError".
-- Base interface functions are in:
--
--     * "JSDOM.DOMError"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/NavigatorUserMediaError Mozilla NavigatorUserMediaError documentation>
newtype NavigatorUserMediaError = NavigatorUserMediaError { NavigatorUserMediaError -> JSVal
unNavigatorUserMediaError :: JSVal }

instance PToJSVal NavigatorUserMediaError where
  pToJSVal :: NavigatorUserMediaError -> JSVal
pToJSVal = NavigatorUserMediaError -> JSVal
unNavigatorUserMediaError
  {-# INLINE pToJSVal #-}

instance PFromJSVal NavigatorUserMediaError where
  pFromJSVal :: JSVal -> NavigatorUserMediaError
pFromJSVal = JSVal -> NavigatorUserMediaError
NavigatorUserMediaError
  {-# INLINE pFromJSVal #-}

instance ToJSVal NavigatorUserMediaError where
  toJSVal :: NavigatorUserMediaError -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NavigatorUserMediaError -> JSVal)
-> NavigatorUserMediaError
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NavigatorUserMediaError -> JSVal
unNavigatorUserMediaError
  {-# INLINE toJSVal #-}

instance FromJSVal NavigatorUserMediaError where
  fromJSVal :: JSVal -> JSM (Maybe NavigatorUserMediaError)
fromJSVal JSVal
v = (JSVal -> NavigatorUserMediaError)
-> Maybe JSVal -> Maybe NavigatorUserMediaError
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NavigatorUserMediaError
NavigatorUserMediaError (Maybe JSVal -> Maybe NavigatorUserMediaError)
-> JSM (Maybe JSVal) -> JSM (Maybe NavigatorUserMediaError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NavigatorUserMediaError
fromJSValUnchecked = NavigatorUserMediaError -> JSM NavigatorUserMediaError
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NavigatorUserMediaError -> JSM NavigatorUserMediaError)
-> (JSVal -> NavigatorUserMediaError)
-> JSVal
-> JSM NavigatorUserMediaError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NavigatorUserMediaError
NavigatorUserMediaError
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NavigatorUserMediaError where
  makeObject :: NavigatorUserMediaError -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NavigatorUserMediaError -> JSVal)
-> NavigatorUserMediaError
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NavigatorUserMediaError -> JSVal
unNavigatorUserMediaError

instance IsDOMError NavigatorUserMediaError
instance IsGObject NavigatorUserMediaError where
  typeGType :: NavigatorUserMediaError -> JSM GType
typeGType NavigatorUserMediaError
_ = JSM GType
gTypeNavigatorUserMediaError
  {-# INLINE typeGType #-}

noNavigatorUserMediaError :: Maybe NavigatorUserMediaError
noNavigatorUserMediaError :: Maybe NavigatorUserMediaError
noNavigatorUserMediaError = Maybe NavigatorUserMediaError
forall a. Maybe a
Nothing
{-# INLINE noNavigatorUserMediaError #-}

gTypeNavigatorUserMediaError :: JSM GType
gTypeNavigatorUserMediaError :: JSM GType
gTypeNavigatorUserMediaError = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"NavigatorUserMediaError"

-- | Functions for this inteface are in "JSDOM.Node".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Node Mozilla Node documentation>
newtype Node = Node { Node -> JSVal
unNode :: JSVal }

instance PToJSVal Node where
  pToJSVal :: Node -> JSVal
pToJSVal = Node -> JSVal
unNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal Node where
  pFromJSVal :: JSVal -> Node
pFromJSVal = JSVal -> Node
Node
  {-# INLINE pFromJSVal #-}

instance ToJSVal Node where
  toJSVal :: Node -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Node -> JSVal) -> Node -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> JSVal
unNode
  {-# INLINE toJSVal #-}

instance FromJSVal Node where
  fromJSVal :: JSVal -> JSM (Maybe Node)
fromJSVal JSVal
v = (JSVal -> Node) -> Maybe JSVal -> Maybe Node
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Node
Node (Maybe JSVal -> Maybe Node)
-> JSM (Maybe JSVal) -> JSM (Maybe Node)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Node
fromJSValUnchecked = Node -> JSM Node
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Node -> JSM Node) -> (JSVal -> Node) -> JSVal -> JSM Node
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Node
Node
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Node where
  makeObject :: Node -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Node -> JSVal) -> Node -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> JSVal
unNode

class (IsEventTarget o, IsGObject o) => IsNode o
toNode :: IsNode o => o -> Node
toNode :: forall o. IsNode o => o -> Node
toNode = JSVal -> Node
Node (JSVal -> Node) -> (o -> JSVal) -> o -> Node
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsNode Node
instance IsEventTarget Node
instance IsGObject Node where
  typeGType :: Node -> JSM GType
typeGType Node
_ = JSM GType
gTypeNode
  {-# INLINE typeGType #-}

noNode :: Maybe Node
noNode :: Maybe Node
noNode = Maybe Node
forall a. Maybe a
Nothing
{-# INLINE noNode #-}

gTypeNode :: JSM GType
gTypeNode :: JSM GType
gTypeNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Node"

-- | Functions for this inteface are in "JSDOM.NodeIterator".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/NodeIterator Mozilla NodeIterator documentation>
newtype NodeIterator = NodeIterator { NodeIterator -> JSVal
unNodeIterator :: JSVal }

instance PToJSVal NodeIterator where
  pToJSVal :: NodeIterator -> JSVal
pToJSVal = NodeIterator -> JSVal
unNodeIterator
  {-# INLINE pToJSVal #-}

instance PFromJSVal NodeIterator where
  pFromJSVal :: JSVal -> NodeIterator
pFromJSVal = JSVal -> NodeIterator
NodeIterator
  {-# INLINE pFromJSVal #-}

instance ToJSVal NodeIterator where
  toJSVal :: NodeIterator -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NodeIterator -> JSVal) -> NodeIterator -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NodeIterator -> JSVal
unNodeIterator
  {-# INLINE toJSVal #-}

instance FromJSVal NodeIterator where
  fromJSVal :: JSVal -> JSM (Maybe NodeIterator)
fromJSVal JSVal
v = (JSVal -> NodeIterator) -> Maybe JSVal -> Maybe NodeIterator
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NodeIterator
NodeIterator (Maybe JSVal -> Maybe NodeIterator)
-> JSM (Maybe JSVal) -> JSM (Maybe NodeIterator)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NodeIterator
fromJSValUnchecked = NodeIterator -> JSM NodeIterator
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NodeIterator -> JSM NodeIterator)
-> (JSVal -> NodeIterator) -> JSVal -> JSM NodeIterator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NodeIterator
NodeIterator
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NodeIterator where
  makeObject :: NodeIterator -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NodeIterator -> JSVal) -> NodeIterator -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NodeIterator -> JSVal
unNodeIterator

instance IsGObject NodeIterator where
  typeGType :: NodeIterator -> JSM GType
typeGType NodeIterator
_ = JSM GType
gTypeNodeIterator
  {-# INLINE typeGType #-}

noNodeIterator :: Maybe NodeIterator
noNodeIterator :: Maybe NodeIterator
noNodeIterator = Maybe NodeIterator
forall a. Maybe a
Nothing
{-# INLINE noNodeIterator #-}

gTypeNodeIterator :: JSM GType
gTypeNodeIterator :: JSM GType
gTypeNodeIterator = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"NodeIterator"

-- | Functions for this inteface are in "JSDOM.NodeList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/NodeList Mozilla NodeList documentation>
newtype NodeList = NodeList { NodeList -> JSVal
unNodeList :: JSVal }

instance PToJSVal NodeList where
  pToJSVal :: NodeList -> JSVal
pToJSVal = NodeList -> JSVal
unNodeList
  {-# INLINE pToJSVal #-}

instance PFromJSVal NodeList where
  pFromJSVal :: JSVal -> NodeList
pFromJSVal = JSVal -> NodeList
NodeList
  {-# INLINE pFromJSVal #-}

instance ToJSVal NodeList where
  toJSVal :: NodeList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NodeList -> JSVal) -> NodeList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NodeList -> JSVal
unNodeList
  {-# INLINE toJSVal #-}

instance FromJSVal NodeList where
  fromJSVal :: JSVal -> JSM (Maybe NodeList)
fromJSVal JSVal
v = (JSVal -> NodeList) -> Maybe JSVal -> Maybe NodeList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NodeList
NodeList (Maybe JSVal -> Maybe NodeList)
-> JSM (Maybe JSVal) -> JSM (Maybe NodeList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NodeList
fromJSValUnchecked = NodeList -> JSM NodeList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NodeList -> JSM NodeList)
-> (JSVal -> NodeList) -> JSVal -> JSM NodeList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NodeList
NodeList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NodeList where
  makeObject :: NodeList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NodeList -> JSVal) -> NodeList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NodeList -> JSVal
unNodeList

class (IsGObject o) => IsNodeList o
toNodeList :: IsNodeList o => o -> NodeList
toNodeList :: forall o. IsNodeList o => o -> NodeList
toNodeList = JSVal -> NodeList
NodeList (JSVal -> NodeList) -> (o -> JSVal) -> o -> NodeList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsNodeList NodeList
instance IsGObject NodeList where
  typeGType :: NodeList -> JSM GType
typeGType NodeList
_ = JSM GType
gTypeNodeList
  {-# INLINE typeGType #-}

noNodeList :: Maybe NodeList
noNodeList :: Maybe NodeList
noNodeList = Maybe NodeList
forall a. Maybe a
Nothing
{-# INLINE noNodeList #-}

gTypeNodeList :: JSM GType
gTypeNodeList :: JSM GType
gTypeNodeList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"NodeList"

-- | Functions for this inteface are in "JSDOM.NonDocumentTypeChildNode".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/NonDocumentTypeChildNode Mozilla NonDocumentTypeChildNode documentation>
newtype NonDocumentTypeChildNode = NonDocumentTypeChildNode { NonDocumentTypeChildNode -> JSVal
unNonDocumentTypeChildNode :: JSVal }

instance PToJSVal NonDocumentTypeChildNode where
  pToJSVal :: NonDocumentTypeChildNode -> JSVal
pToJSVal = NonDocumentTypeChildNode -> JSVal
unNonDocumentTypeChildNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal NonDocumentTypeChildNode where
  pFromJSVal :: JSVal -> NonDocumentTypeChildNode
pFromJSVal = JSVal -> NonDocumentTypeChildNode
NonDocumentTypeChildNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal NonDocumentTypeChildNode where
  toJSVal :: NonDocumentTypeChildNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NonDocumentTypeChildNode -> JSVal)
-> NonDocumentTypeChildNode
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonDocumentTypeChildNode -> JSVal
unNonDocumentTypeChildNode
  {-# INLINE toJSVal #-}

instance FromJSVal NonDocumentTypeChildNode where
  fromJSVal :: JSVal -> JSM (Maybe NonDocumentTypeChildNode)
fromJSVal JSVal
v = (JSVal -> NonDocumentTypeChildNode)
-> Maybe JSVal -> Maybe NonDocumentTypeChildNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NonDocumentTypeChildNode
NonDocumentTypeChildNode (Maybe JSVal -> Maybe NonDocumentTypeChildNode)
-> JSM (Maybe JSVal) -> JSM (Maybe NonDocumentTypeChildNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NonDocumentTypeChildNode
fromJSValUnchecked = NonDocumentTypeChildNode -> JSM NonDocumentTypeChildNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NonDocumentTypeChildNode -> JSM NonDocumentTypeChildNode)
-> (JSVal -> NonDocumentTypeChildNode)
-> JSVal
-> JSM NonDocumentTypeChildNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NonDocumentTypeChildNode
NonDocumentTypeChildNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NonDocumentTypeChildNode where
  makeObject :: NonDocumentTypeChildNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NonDocumentTypeChildNode -> JSVal)
-> NonDocumentTypeChildNode
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonDocumentTypeChildNode -> JSVal
unNonDocumentTypeChildNode

class (IsGObject o) => IsNonDocumentTypeChildNode o
toNonDocumentTypeChildNode :: IsNonDocumentTypeChildNode o => o -> NonDocumentTypeChildNode
toNonDocumentTypeChildNode :: forall o.
IsNonDocumentTypeChildNode o =>
o -> NonDocumentTypeChildNode
toNonDocumentTypeChildNode = JSVal -> NonDocumentTypeChildNode
NonDocumentTypeChildNode (JSVal -> NonDocumentTypeChildNode)
-> (o -> JSVal) -> o -> NonDocumentTypeChildNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsNonDocumentTypeChildNode NonDocumentTypeChildNode
instance IsGObject NonDocumentTypeChildNode where
  typeGType :: NonDocumentTypeChildNode -> JSM GType
typeGType NonDocumentTypeChildNode
_ = JSM GType
gTypeNonDocumentTypeChildNode
  {-# INLINE typeGType #-}

noNonDocumentTypeChildNode :: Maybe NonDocumentTypeChildNode
noNonDocumentTypeChildNode :: Maybe NonDocumentTypeChildNode
noNonDocumentTypeChildNode = Maybe NonDocumentTypeChildNode
forall a. Maybe a
Nothing
{-# INLINE noNonDocumentTypeChildNode #-}

gTypeNonDocumentTypeChildNode :: JSM GType
gTypeNonDocumentTypeChildNode :: JSM GType
gTypeNonDocumentTypeChildNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"NonDocumentTypeChildNode"

-- | Functions for this inteface are in "JSDOM.NonElementParentNode".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/NonElementParentNode Mozilla NonElementParentNode documentation>
newtype NonElementParentNode = NonElementParentNode { NonElementParentNode -> JSVal
unNonElementParentNode :: JSVal }

instance PToJSVal NonElementParentNode where
  pToJSVal :: NonElementParentNode -> JSVal
pToJSVal = NonElementParentNode -> JSVal
unNonElementParentNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal NonElementParentNode where
  pFromJSVal :: JSVal -> NonElementParentNode
pFromJSVal = JSVal -> NonElementParentNode
NonElementParentNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal NonElementParentNode where
  toJSVal :: NonElementParentNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NonElementParentNode -> JSVal)
-> NonElementParentNode
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonElementParentNode -> JSVal
unNonElementParentNode
  {-# INLINE toJSVal #-}

instance FromJSVal NonElementParentNode where
  fromJSVal :: JSVal -> JSM (Maybe NonElementParentNode)
fromJSVal JSVal
v = (JSVal -> NonElementParentNode)
-> Maybe JSVal -> Maybe NonElementParentNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NonElementParentNode
NonElementParentNode (Maybe JSVal -> Maybe NonElementParentNode)
-> JSM (Maybe JSVal) -> JSM (Maybe NonElementParentNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NonElementParentNode
fromJSValUnchecked = NonElementParentNode -> JSM NonElementParentNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NonElementParentNode -> JSM NonElementParentNode)
-> (JSVal -> NonElementParentNode)
-> JSVal
-> JSM NonElementParentNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NonElementParentNode
NonElementParentNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NonElementParentNode where
  makeObject :: NonElementParentNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NonElementParentNode -> JSVal)
-> NonElementParentNode
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonElementParentNode -> JSVal
unNonElementParentNode

class (IsGObject o) => IsNonElementParentNode o
toNonElementParentNode :: IsNonElementParentNode o => o -> NonElementParentNode
toNonElementParentNode :: forall o. IsNonElementParentNode o => o -> NonElementParentNode
toNonElementParentNode = JSVal -> NonElementParentNode
NonElementParentNode (JSVal -> NonElementParentNode)
-> (o -> JSVal) -> o -> NonElementParentNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsNonElementParentNode NonElementParentNode
instance IsGObject NonElementParentNode where
  typeGType :: NonElementParentNode -> JSM GType
typeGType NonElementParentNode
_ = JSM GType
gTypeNonElementParentNode
  {-# INLINE typeGType #-}

noNonElementParentNode :: Maybe NonElementParentNode
noNonElementParentNode :: Maybe NonElementParentNode
noNonElementParentNode = Maybe NonElementParentNode
forall a. Maybe a
Nothing
{-# INLINE noNonElementParentNode #-}

gTypeNonElementParentNode :: JSM GType
gTypeNonElementParentNode :: JSM GType
gTypeNonElementParentNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"NonElementParentNode"

-- | Functions for this inteface are in "JSDOM.Notification".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Notification Mozilla Notification documentation>
newtype Notification = Notification { Notification -> JSVal
unNotification :: JSVal }

instance PToJSVal Notification where
  pToJSVal :: Notification -> JSVal
pToJSVal = Notification -> JSVal
unNotification
  {-# INLINE pToJSVal #-}

instance PFromJSVal Notification where
  pFromJSVal :: JSVal -> Notification
pFromJSVal = JSVal -> Notification
Notification
  {-# INLINE pFromJSVal #-}

instance ToJSVal Notification where
  toJSVal :: Notification -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Notification -> JSVal) -> Notification -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Notification -> JSVal
unNotification
  {-# INLINE toJSVal #-}

instance FromJSVal Notification where
  fromJSVal :: JSVal -> JSM (Maybe Notification)
fromJSVal JSVal
v = (JSVal -> Notification) -> Maybe JSVal -> Maybe Notification
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Notification
Notification (Maybe JSVal -> Maybe Notification)
-> JSM (Maybe JSVal) -> JSM (Maybe Notification)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Notification
fromJSValUnchecked = Notification -> JSM Notification
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Notification -> JSM Notification)
-> (JSVal -> Notification) -> JSVal -> JSM Notification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Notification
Notification
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Notification where
  makeObject :: Notification -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Notification -> JSVal) -> Notification -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Notification -> JSVal
unNotification

instance IsEventTarget Notification
instance IsGObject Notification where
  typeGType :: Notification -> JSM GType
typeGType Notification
_ = JSM GType
gTypeNotification
  {-# INLINE typeGType #-}

noNotification :: Maybe Notification
noNotification :: Maybe Notification
noNotification = Maybe Notification
forall a. Maybe a
Nothing
{-# INLINE noNotification #-}

gTypeNotification :: JSM GType
gTypeNotification :: JSM GType
gTypeNotification = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Notification"

-- | Functions for this inteface are in "JSDOM.NotificationOptions".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/NotificationOptions Mozilla NotificationOptions documentation>
newtype NotificationOptions = NotificationOptions { NotificationOptions -> JSVal
unNotificationOptions :: JSVal }

instance PToJSVal NotificationOptions where
  pToJSVal :: NotificationOptions -> JSVal
pToJSVal = NotificationOptions -> JSVal
unNotificationOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal NotificationOptions where
  pFromJSVal :: JSVal -> NotificationOptions
pFromJSVal = JSVal -> NotificationOptions
NotificationOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal NotificationOptions where
  toJSVal :: NotificationOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (NotificationOptions -> JSVal)
-> NotificationOptions
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NotificationOptions -> JSVal
unNotificationOptions
  {-# INLINE toJSVal #-}

instance FromJSVal NotificationOptions where
  fromJSVal :: JSVal -> JSM (Maybe NotificationOptions)
fromJSVal JSVal
v = (JSVal -> NotificationOptions)
-> Maybe JSVal -> Maybe NotificationOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> NotificationOptions
NotificationOptions (Maybe JSVal -> Maybe NotificationOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe NotificationOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM NotificationOptions
fromJSValUnchecked = NotificationOptions -> JSM NotificationOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (NotificationOptions -> JSM NotificationOptions)
-> (JSVal -> NotificationOptions)
-> JSVal
-> JSM NotificationOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> NotificationOptions
NotificationOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject NotificationOptions where
  makeObject :: NotificationOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (NotificationOptions -> JSVal)
-> NotificationOptions
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NotificationOptions -> JSVal
unNotificationOptions

instance IsGObject NotificationOptions where
  typeGType :: NotificationOptions -> JSM GType
typeGType NotificationOptions
_ = JSM GType
gTypeNotificationOptions
  {-# INLINE typeGType #-}

noNotificationOptions :: Maybe NotificationOptions
noNotificationOptions :: Maybe NotificationOptions
noNotificationOptions = Maybe NotificationOptions
forall a. Maybe a
Nothing
{-# INLINE noNotificationOptions #-}

gTypeNotificationOptions :: JSM GType
gTypeNotificationOptions :: JSM GType
gTypeNotificationOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"NotificationOptions"

-- | Functions for this inteface are in "JSDOM.OESElementIndexUint".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OESElementIndexUint Mozilla OESElementIndexUint documentation>
newtype OESElementIndexUint = OESElementIndexUint { OESElementIndexUint -> JSVal
unOESElementIndexUint :: JSVal }

instance PToJSVal OESElementIndexUint where
  pToJSVal :: OESElementIndexUint -> JSVal
pToJSVal = OESElementIndexUint -> JSVal
unOESElementIndexUint
  {-# INLINE pToJSVal #-}

instance PFromJSVal OESElementIndexUint where
  pFromJSVal :: JSVal -> OESElementIndexUint
pFromJSVal = JSVal -> OESElementIndexUint
OESElementIndexUint
  {-# INLINE pFromJSVal #-}

instance ToJSVal OESElementIndexUint where
  toJSVal :: OESElementIndexUint -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OESElementIndexUint -> JSVal)
-> OESElementIndexUint
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESElementIndexUint -> JSVal
unOESElementIndexUint
  {-# INLINE toJSVal #-}

instance FromJSVal OESElementIndexUint where
  fromJSVal :: JSVal -> JSM (Maybe OESElementIndexUint)
fromJSVal JSVal
v = (JSVal -> OESElementIndexUint)
-> Maybe JSVal -> Maybe OESElementIndexUint
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OESElementIndexUint
OESElementIndexUint (Maybe JSVal -> Maybe OESElementIndexUint)
-> JSM (Maybe JSVal) -> JSM (Maybe OESElementIndexUint)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OESElementIndexUint
fromJSValUnchecked = OESElementIndexUint -> JSM OESElementIndexUint
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OESElementIndexUint -> JSM OESElementIndexUint)
-> (JSVal -> OESElementIndexUint)
-> JSVal
-> JSM OESElementIndexUint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OESElementIndexUint
OESElementIndexUint
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OESElementIndexUint where
  makeObject :: OESElementIndexUint -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OESElementIndexUint -> JSVal)
-> OESElementIndexUint
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESElementIndexUint -> JSVal
unOESElementIndexUint

instance IsGObject OESElementIndexUint where
  typeGType :: OESElementIndexUint -> JSM GType
typeGType OESElementIndexUint
_ = JSM GType
gTypeOESElementIndexUint
  {-# INLINE typeGType #-}

noOESElementIndexUint :: Maybe OESElementIndexUint
noOESElementIndexUint :: Maybe OESElementIndexUint
noOESElementIndexUint = Maybe OESElementIndexUint
forall a. Maybe a
Nothing
{-# INLINE noOESElementIndexUint #-}

gTypeOESElementIndexUint :: JSM GType
gTypeOESElementIndexUint :: JSM GType
gTypeOESElementIndexUint = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OESElementIndexUint"

-- | Functions for this inteface are in "JSDOM.OESStandardDerivatives".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OESStandardDerivatives Mozilla OESStandardDerivatives documentation>
newtype OESStandardDerivatives = OESStandardDerivatives { OESStandardDerivatives -> JSVal
unOESStandardDerivatives :: JSVal }

instance PToJSVal OESStandardDerivatives where
  pToJSVal :: OESStandardDerivatives -> JSVal
pToJSVal = OESStandardDerivatives -> JSVal
unOESStandardDerivatives
  {-# INLINE pToJSVal #-}

instance PFromJSVal OESStandardDerivatives where
  pFromJSVal :: JSVal -> OESStandardDerivatives
pFromJSVal = JSVal -> OESStandardDerivatives
OESStandardDerivatives
  {-# INLINE pFromJSVal #-}

instance ToJSVal OESStandardDerivatives where
  toJSVal :: OESStandardDerivatives -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OESStandardDerivatives -> JSVal)
-> OESStandardDerivatives
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESStandardDerivatives -> JSVal
unOESStandardDerivatives
  {-# INLINE toJSVal #-}

instance FromJSVal OESStandardDerivatives where
  fromJSVal :: JSVal -> JSM (Maybe OESStandardDerivatives)
fromJSVal JSVal
v = (JSVal -> OESStandardDerivatives)
-> Maybe JSVal -> Maybe OESStandardDerivatives
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OESStandardDerivatives
OESStandardDerivatives (Maybe JSVal -> Maybe OESStandardDerivatives)
-> JSM (Maybe JSVal) -> JSM (Maybe OESStandardDerivatives)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OESStandardDerivatives
fromJSValUnchecked = OESStandardDerivatives -> JSM OESStandardDerivatives
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OESStandardDerivatives -> JSM OESStandardDerivatives)
-> (JSVal -> OESStandardDerivatives)
-> JSVal
-> JSM OESStandardDerivatives
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OESStandardDerivatives
OESStandardDerivatives
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OESStandardDerivatives where
  makeObject :: OESStandardDerivatives -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OESStandardDerivatives -> JSVal)
-> OESStandardDerivatives
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESStandardDerivatives -> JSVal
unOESStandardDerivatives

instance IsGObject OESStandardDerivatives where
  typeGType :: OESStandardDerivatives -> JSM GType
typeGType OESStandardDerivatives
_ = JSM GType
gTypeOESStandardDerivatives
  {-# INLINE typeGType #-}

noOESStandardDerivatives :: Maybe OESStandardDerivatives
noOESStandardDerivatives :: Maybe OESStandardDerivatives
noOESStandardDerivatives = Maybe OESStandardDerivatives
forall a. Maybe a
Nothing
{-# INLINE noOESStandardDerivatives #-}

gTypeOESStandardDerivatives :: JSM GType
gTypeOESStandardDerivatives :: JSM GType
gTypeOESStandardDerivatives = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OESStandardDerivatives"

-- | Functions for this inteface are in "JSDOM.OESTextureFloat".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OESTextureFloat Mozilla OESTextureFloat documentation>
newtype OESTextureFloat = OESTextureFloat { OESTextureFloat -> JSVal
unOESTextureFloat :: JSVal }

instance PToJSVal OESTextureFloat where
  pToJSVal :: OESTextureFloat -> JSVal
pToJSVal = OESTextureFloat -> JSVal
unOESTextureFloat
  {-# INLINE pToJSVal #-}

instance PFromJSVal OESTextureFloat where
  pFromJSVal :: JSVal -> OESTextureFloat
pFromJSVal = JSVal -> OESTextureFloat
OESTextureFloat
  {-# INLINE pFromJSVal #-}

instance ToJSVal OESTextureFloat where
  toJSVal :: OESTextureFloat -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OESTextureFloat -> JSVal) -> OESTextureFloat -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESTextureFloat -> JSVal
unOESTextureFloat
  {-# INLINE toJSVal #-}

instance FromJSVal OESTextureFloat where
  fromJSVal :: JSVal -> JSM (Maybe OESTextureFloat)
fromJSVal JSVal
v = (JSVal -> OESTextureFloat) -> Maybe JSVal -> Maybe OESTextureFloat
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OESTextureFloat
OESTextureFloat (Maybe JSVal -> Maybe OESTextureFloat)
-> JSM (Maybe JSVal) -> JSM (Maybe OESTextureFloat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OESTextureFloat
fromJSValUnchecked = OESTextureFloat -> JSM OESTextureFloat
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OESTextureFloat -> JSM OESTextureFloat)
-> (JSVal -> OESTextureFloat) -> JSVal -> JSM OESTextureFloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OESTextureFloat
OESTextureFloat
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OESTextureFloat where
  makeObject :: OESTextureFloat -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OESTextureFloat -> JSVal) -> OESTextureFloat -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESTextureFloat -> JSVal
unOESTextureFloat

instance IsGObject OESTextureFloat where
  typeGType :: OESTextureFloat -> JSM GType
typeGType OESTextureFloat
_ = JSM GType
gTypeOESTextureFloat
  {-# INLINE typeGType #-}

noOESTextureFloat :: Maybe OESTextureFloat
noOESTextureFloat :: Maybe OESTextureFloat
noOESTextureFloat = Maybe OESTextureFloat
forall a. Maybe a
Nothing
{-# INLINE noOESTextureFloat #-}

gTypeOESTextureFloat :: JSM GType
gTypeOESTextureFloat :: JSM GType
gTypeOESTextureFloat = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OESTextureFloat"

-- | Functions for this inteface are in "JSDOM.OESTextureFloatLinear".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OESTextureFloatLinear Mozilla OESTextureFloatLinear documentation>
newtype OESTextureFloatLinear = OESTextureFloatLinear { OESTextureFloatLinear -> JSVal
unOESTextureFloatLinear :: JSVal }

instance PToJSVal OESTextureFloatLinear where
  pToJSVal :: OESTextureFloatLinear -> JSVal
pToJSVal = OESTextureFloatLinear -> JSVal
unOESTextureFloatLinear
  {-# INLINE pToJSVal #-}

instance PFromJSVal OESTextureFloatLinear where
  pFromJSVal :: JSVal -> OESTextureFloatLinear
pFromJSVal = JSVal -> OESTextureFloatLinear
OESTextureFloatLinear
  {-# INLINE pFromJSVal #-}

instance ToJSVal OESTextureFloatLinear where
  toJSVal :: OESTextureFloatLinear -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OESTextureFloatLinear -> JSVal)
-> OESTextureFloatLinear
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESTextureFloatLinear -> JSVal
unOESTextureFloatLinear
  {-# INLINE toJSVal #-}

instance FromJSVal OESTextureFloatLinear where
  fromJSVal :: JSVal -> JSM (Maybe OESTextureFloatLinear)
fromJSVal JSVal
v = (JSVal -> OESTextureFloatLinear)
-> Maybe JSVal -> Maybe OESTextureFloatLinear
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OESTextureFloatLinear
OESTextureFloatLinear (Maybe JSVal -> Maybe OESTextureFloatLinear)
-> JSM (Maybe JSVal) -> JSM (Maybe OESTextureFloatLinear)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OESTextureFloatLinear
fromJSValUnchecked = OESTextureFloatLinear -> JSM OESTextureFloatLinear
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OESTextureFloatLinear -> JSM OESTextureFloatLinear)
-> (JSVal -> OESTextureFloatLinear)
-> JSVal
-> JSM OESTextureFloatLinear
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OESTextureFloatLinear
OESTextureFloatLinear
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OESTextureFloatLinear where
  makeObject :: OESTextureFloatLinear -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OESTextureFloatLinear -> JSVal)
-> OESTextureFloatLinear
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESTextureFloatLinear -> JSVal
unOESTextureFloatLinear

instance IsGObject OESTextureFloatLinear where
  typeGType :: OESTextureFloatLinear -> JSM GType
typeGType OESTextureFloatLinear
_ = JSM GType
gTypeOESTextureFloatLinear
  {-# INLINE typeGType #-}

noOESTextureFloatLinear :: Maybe OESTextureFloatLinear
noOESTextureFloatLinear :: Maybe OESTextureFloatLinear
noOESTextureFloatLinear = Maybe OESTextureFloatLinear
forall a. Maybe a
Nothing
{-# INLINE noOESTextureFloatLinear #-}

gTypeOESTextureFloatLinear :: JSM GType
gTypeOESTextureFloatLinear :: JSM GType
gTypeOESTextureFloatLinear = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OESTextureFloatLinear"

-- | Functions for this inteface are in "JSDOM.OESTextureHalfFloat".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OESTextureHalfFloat Mozilla OESTextureHalfFloat documentation>
newtype OESTextureHalfFloat = OESTextureHalfFloat { OESTextureHalfFloat -> JSVal
unOESTextureHalfFloat :: JSVal }

instance PToJSVal OESTextureHalfFloat where
  pToJSVal :: OESTextureHalfFloat -> JSVal
pToJSVal = OESTextureHalfFloat -> JSVal
unOESTextureHalfFloat
  {-# INLINE pToJSVal #-}

instance PFromJSVal OESTextureHalfFloat where
  pFromJSVal :: JSVal -> OESTextureHalfFloat
pFromJSVal = JSVal -> OESTextureHalfFloat
OESTextureHalfFloat
  {-# INLINE pFromJSVal #-}

instance ToJSVal OESTextureHalfFloat where
  toJSVal :: OESTextureHalfFloat -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OESTextureHalfFloat -> JSVal)
-> OESTextureHalfFloat
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESTextureHalfFloat -> JSVal
unOESTextureHalfFloat
  {-# INLINE toJSVal #-}

instance FromJSVal OESTextureHalfFloat where
  fromJSVal :: JSVal -> JSM (Maybe OESTextureHalfFloat)
fromJSVal JSVal
v = (JSVal -> OESTextureHalfFloat)
-> Maybe JSVal -> Maybe OESTextureHalfFloat
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OESTextureHalfFloat
OESTextureHalfFloat (Maybe JSVal -> Maybe OESTextureHalfFloat)
-> JSM (Maybe JSVal) -> JSM (Maybe OESTextureHalfFloat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OESTextureHalfFloat
fromJSValUnchecked = OESTextureHalfFloat -> JSM OESTextureHalfFloat
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OESTextureHalfFloat -> JSM OESTextureHalfFloat)
-> (JSVal -> OESTextureHalfFloat)
-> JSVal
-> JSM OESTextureHalfFloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OESTextureHalfFloat
OESTextureHalfFloat
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OESTextureHalfFloat where
  makeObject :: OESTextureHalfFloat -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OESTextureHalfFloat -> JSVal)
-> OESTextureHalfFloat
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESTextureHalfFloat -> JSVal
unOESTextureHalfFloat

instance IsGObject OESTextureHalfFloat where
  typeGType :: OESTextureHalfFloat -> JSM GType
typeGType OESTextureHalfFloat
_ = JSM GType
gTypeOESTextureHalfFloat
  {-# INLINE typeGType #-}

noOESTextureHalfFloat :: Maybe OESTextureHalfFloat
noOESTextureHalfFloat :: Maybe OESTextureHalfFloat
noOESTextureHalfFloat = Maybe OESTextureHalfFloat
forall a. Maybe a
Nothing
{-# INLINE noOESTextureHalfFloat #-}

gTypeOESTextureHalfFloat :: JSM GType
gTypeOESTextureHalfFloat :: JSM GType
gTypeOESTextureHalfFloat = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OESTextureHalfFloat"

-- | Functions for this inteface are in "JSDOM.OESTextureHalfFloatLinear".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OESTextureHalfFloatLinear Mozilla OESTextureHalfFloatLinear documentation>
newtype OESTextureHalfFloatLinear = OESTextureHalfFloatLinear { OESTextureHalfFloatLinear -> JSVal
unOESTextureHalfFloatLinear :: JSVal }

instance PToJSVal OESTextureHalfFloatLinear where
  pToJSVal :: OESTextureHalfFloatLinear -> JSVal
pToJSVal = OESTextureHalfFloatLinear -> JSVal
unOESTextureHalfFloatLinear
  {-# INLINE pToJSVal #-}

instance PFromJSVal OESTextureHalfFloatLinear where
  pFromJSVal :: JSVal -> OESTextureHalfFloatLinear
pFromJSVal = JSVal -> OESTextureHalfFloatLinear
OESTextureHalfFloatLinear
  {-# INLINE pFromJSVal #-}

instance ToJSVal OESTextureHalfFloatLinear where
  toJSVal :: OESTextureHalfFloatLinear -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OESTextureHalfFloatLinear -> JSVal)
-> OESTextureHalfFloatLinear
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESTextureHalfFloatLinear -> JSVal
unOESTextureHalfFloatLinear
  {-# INLINE toJSVal #-}

instance FromJSVal OESTextureHalfFloatLinear where
  fromJSVal :: JSVal -> JSM (Maybe OESTextureHalfFloatLinear)
fromJSVal JSVal
v = (JSVal -> OESTextureHalfFloatLinear)
-> Maybe JSVal -> Maybe OESTextureHalfFloatLinear
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OESTextureHalfFloatLinear
OESTextureHalfFloatLinear (Maybe JSVal -> Maybe OESTextureHalfFloatLinear)
-> JSM (Maybe JSVal) -> JSM (Maybe OESTextureHalfFloatLinear)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OESTextureHalfFloatLinear
fromJSValUnchecked = OESTextureHalfFloatLinear -> JSM OESTextureHalfFloatLinear
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OESTextureHalfFloatLinear -> JSM OESTextureHalfFloatLinear)
-> (JSVal -> OESTextureHalfFloatLinear)
-> JSVal
-> JSM OESTextureHalfFloatLinear
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OESTextureHalfFloatLinear
OESTextureHalfFloatLinear
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OESTextureHalfFloatLinear where
  makeObject :: OESTextureHalfFloatLinear -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OESTextureHalfFloatLinear -> JSVal)
-> OESTextureHalfFloatLinear
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESTextureHalfFloatLinear -> JSVal
unOESTextureHalfFloatLinear

instance IsGObject OESTextureHalfFloatLinear where
  typeGType :: OESTextureHalfFloatLinear -> JSM GType
typeGType OESTextureHalfFloatLinear
_ = JSM GType
gTypeOESTextureHalfFloatLinear
  {-# INLINE typeGType #-}

noOESTextureHalfFloatLinear :: Maybe OESTextureHalfFloatLinear
noOESTextureHalfFloatLinear :: Maybe OESTextureHalfFloatLinear
noOESTextureHalfFloatLinear = Maybe OESTextureHalfFloatLinear
forall a. Maybe a
Nothing
{-# INLINE noOESTextureHalfFloatLinear #-}

gTypeOESTextureHalfFloatLinear :: JSM GType
gTypeOESTextureHalfFloatLinear :: JSM GType
gTypeOESTextureHalfFloatLinear = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OESTextureHalfFloatLinear"

-- | Functions for this inteface are in "JSDOM.OESVertexArrayObject".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OESVertexArrayObject Mozilla OESVertexArrayObject documentation>
newtype OESVertexArrayObject = OESVertexArrayObject { OESVertexArrayObject -> JSVal
unOESVertexArrayObject :: JSVal }

instance PToJSVal OESVertexArrayObject where
  pToJSVal :: OESVertexArrayObject -> JSVal
pToJSVal = OESVertexArrayObject -> JSVal
unOESVertexArrayObject
  {-# INLINE pToJSVal #-}

instance PFromJSVal OESVertexArrayObject where
  pFromJSVal :: JSVal -> OESVertexArrayObject
pFromJSVal = JSVal -> OESVertexArrayObject
OESVertexArrayObject
  {-# INLINE pFromJSVal #-}

instance ToJSVal OESVertexArrayObject where
  toJSVal :: OESVertexArrayObject -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OESVertexArrayObject -> JSVal)
-> OESVertexArrayObject
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESVertexArrayObject -> JSVal
unOESVertexArrayObject
  {-# INLINE toJSVal #-}

instance FromJSVal OESVertexArrayObject where
  fromJSVal :: JSVal -> JSM (Maybe OESVertexArrayObject)
fromJSVal JSVal
v = (JSVal -> OESVertexArrayObject)
-> Maybe JSVal -> Maybe OESVertexArrayObject
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OESVertexArrayObject
OESVertexArrayObject (Maybe JSVal -> Maybe OESVertexArrayObject)
-> JSM (Maybe JSVal) -> JSM (Maybe OESVertexArrayObject)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OESVertexArrayObject
fromJSValUnchecked = OESVertexArrayObject -> JSM OESVertexArrayObject
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OESVertexArrayObject -> JSM OESVertexArrayObject)
-> (JSVal -> OESVertexArrayObject)
-> JSVal
-> JSM OESVertexArrayObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OESVertexArrayObject
OESVertexArrayObject
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OESVertexArrayObject where
  makeObject :: OESVertexArrayObject -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OESVertexArrayObject -> JSVal)
-> OESVertexArrayObject
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OESVertexArrayObject -> JSVal
unOESVertexArrayObject

instance IsGObject OESVertexArrayObject where
  typeGType :: OESVertexArrayObject -> JSM GType
typeGType OESVertexArrayObject
_ = JSM GType
gTypeOESVertexArrayObject
  {-# INLINE typeGType #-}

noOESVertexArrayObject :: Maybe OESVertexArrayObject
noOESVertexArrayObject :: Maybe OESVertexArrayObject
noOESVertexArrayObject = Maybe OESVertexArrayObject
forall a. Maybe a
Nothing
{-# INLINE noOESVertexArrayObject #-}

gTypeOESVertexArrayObject :: JSM GType
gTypeOESVertexArrayObject :: JSM GType
gTypeOESVertexArrayObject = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OESVertexArrayObject"

-- | Functions for this inteface are in "JSDOM.OfflineAudioCompletionEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OfflineAudioCompletionEvent Mozilla OfflineAudioCompletionEvent documentation>
newtype OfflineAudioCompletionEvent = OfflineAudioCompletionEvent { OfflineAudioCompletionEvent -> JSVal
unOfflineAudioCompletionEvent :: JSVal }

instance PToJSVal OfflineAudioCompletionEvent where
  pToJSVal :: OfflineAudioCompletionEvent -> JSVal
pToJSVal = OfflineAudioCompletionEvent -> JSVal
unOfflineAudioCompletionEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal OfflineAudioCompletionEvent where
  pFromJSVal :: JSVal -> OfflineAudioCompletionEvent
pFromJSVal = JSVal -> OfflineAudioCompletionEvent
OfflineAudioCompletionEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal OfflineAudioCompletionEvent where
  toJSVal :: OfflineAudioCompletionEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OfflineAudioCompletionEvent -> JSVal)
-> OfflineAudioCompletionEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OfflineAudioCompletionEvent -> JSVal
unOfflineAudioCompletionEvent
  {-# INLINE toJSVal #-}

instance FromJSVal OfflineAudioCompletionEvent where
  fromJSVal :: JSVal -> JSM (Maybe OfflineAudioCompletionEvent)
fromJSVal JSVal
v = (JSVal -> OfflineAudioCompletionEvent)
-> Maybe JSVal -> Maybe OfflineAudioCompletionEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OfflineAudioCompletionEvent
OfflineAudioCompletionEvent (Maybe JSVal -> Maybe OfflineAudioCompletionEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe OfflineAudioCompletionEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OfflineAudioCompletionEvent
fromJSValUnchecked = OfflineAudioCompletionEvent -> JSM OfflineAudioCompletionEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OfflineAudioCompletionEvent -> JSM OfflineAudioCompletionEvent)
-> (JSVal -> OfflineAudioCompletionEvent)
-> JSVal
-> JSM OfflineAudioCompletionEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OfflineAudioCompletionEvent
OfflineAudioCompletionEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OfflineAudioCompletionEvent where
  makeObject :: OfflineAudioCompletionEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OfflineAudioCompletionEvent -> JSVal)
-> OfflineAudioCompletionEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OfflineAudioCompletionEvent -> JSVal
unOfflineAudioCompletionEvent

instance IsEvent OfflineAudioCompletionEvent
instance IsGObject OfflineAudioCompletionEvent where
  typeGType :: OfflineAudioCompletionEvent -> JSM GType
typeGType OfflineAudioCompletionEvent
_ = JSM GType
gTypeOfflineAudioCompletionEvent
  {-# INLINE typeGType #-}

noOfflineAudioCompletionEvent :: Maybe OfflineAudioCompletionEvent
noOfflineAudioCompletionEvent :: Maybe OfflineAudioCompletionEvent
noOfflineAudioCompletionEvent = Maybe OfflineAudioCompletionEvent
forall a. Maybe a
Nothing
{-# INLINE noOfflineAudioCompletionEvent #-}

gTypeOfflineAudioCompletionEvent :: JSM GType
gTypeOfflineAudioCompletionEvent :: JSM GType
gTypeOfflineAudioCompletionEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OfflineAudioCompletionEvent"

-- | Functions for this inteface are in "JSDOM.OfflineAudioContext".
-- Base interface functions are in:
--
--     * "JSDOM.AudioContext"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OfflineAudioContext Mozilla OfflineAudioContext documentation>
newtype OfflineAudioContext = OfflineAudioContext { OfflineAudioContext -> JSVal
unOfflineAudioContext :: JSVal }

instance PToJSVal OfflineAudioContext where
  pToJSVal :: OfflineAudioContext -> JSVal
pToJSVal = OfflineAudioContext -> JSVal
unOfflineAudioContext
  {-# INLINE pToJSVal #-}

instance PFromJSVal OfflineAudioContext where
  pFromJSVal :: JSVal -> OfflineAudioContext
pFromJSVal = JSVal -> OfflineAudioContext
OfflineAudioContext
  {-# INLINE pFromJSVal #-}

instance ToJSVal OfflineAudioContext where
  toJSVal :: OfflineAudioContext -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OfflineAudioContext -> JSVal)
-> OfflineAudioContext
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OfflineAudioContext -> JSVal
unOfflineAudioContext
  {-# INLINE toJSVal #-}

instance FromJSVal OfflineAudioContext where
  fromJSVal :: JSVal -> JSM (Maybe OfflineAudioContext)
fromJSVal JSVal
v = (JSVal -> OfflineAudioContext)
-> Maybe JSVal -> Maybe OfflineAudioContext
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OfflineAudioContext
OfflineAudioContext (Maybe JSVal -> Maybe OfflineAudioContext)
-> JSM (Maybe JSVal) -> JSM (Maybe OfflineAudioContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OfflineAudioContext
fromJSValUnchecked = OfflineAudioContext -> JSM OfflineAudioContext
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OfflineAudioContext -> JSM OfflineAudioContext)
-> (JSVal -> OfflineAudioContext)
-> JSVal
-> JSM OfflineAudioContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OfflineAudioContext
OfflineAudioContext
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OfflineAudioContext where
  makeObject :: OfflineAudioContext -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OfflineAudioContext -> JSVal)
-> OfflineAudioContext
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OfflineAudioContext -> JSVal
unOfflineAudioContext

instance IsAudioContext OfflineAudioContext
instance IsEventTarget OfflineAudioContext
instance IsGObject OfflineAudioContext where
  typeGType :: OfflineAudioContext -> JSM GType
typeGType OfflineAudioContext
_ = JSM GType
gTypeOfflineAudioContext
  {-# INLINE typeGType #-}

noOfflineAudioContext :: Maybe OfflineAudioContext
noOfflineAudioContext :: Maybe OfflineAudioContext
noOfflineAudioContext = Maybe OfflineAudioContext
forall a. Maybe a
Nothing
{-# INLINE noOfflineAudioContext #-}

gTypeOfflineAudioContext :: JSM GType
gTypeOfflineAudioContext :: JSM GType
gTypeOfflineAudioContext = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OfflineAudioContext"

-- | Functions for this inteface are in "JSDOM.OscillatorNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OscillatorNode Mozilla OscillatorNode documentation>
newtype OscillatorNode = OscillatorNode { OscillatorNode -> JSVal
unOscillatorNode :: JSVal }

instance PToJSVal OscillatorNode where
  pToJSVal :: OscillatorNode -> JSVal
pToJSVal = OscillatorNode -> JSVal
unOscillatorNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal OscillatorNode where
  pFromJSVal :: JSVal -> OscillatorNode
pFromJSVal = JSVal -> OscillatorNode
OscillatorNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal OscillatorNode where
  toJSVal :: OscillatorNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OscillatorNode -> JSVal) -> OscillatorNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OscillatorNode -> JSVal
unOscillatorNode
  {-# INLINE toJSVal #-}

instance FromJSVal OscillatorNode where
  fromJSVal :: JSVal -> JSM (Maybe OscillatorNode)
fromJSVal JSVal
v = (JSVal -> OscillatorNode) -> Maybe JSVal -> Maybe OscillatorNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OscillatorNode
OscillatorNode (Maybe JSVal -> Maybe OscillatorNode)
-> JSM (Maybe JSVal) -> JSM (Maybe OscillatorNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OscillatorNode
fromJSValUnchecked = OscillatorNode -> JSM OscillatorNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OscillatorNode -> JSM OscillatorNode)
-> (JSVal -> OscillatorNode) -> JSVal -> JSM OscillatorNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OscillatorNode
OscillatorNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OscillatorNode where
  makeObject :: OscillatorNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OscillatorNode -> JSVal) -> OscillatorNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OscillatorNode -> JSVal
unOscillatorNode

instance IsAudioNode OscillatorNode
instance IsEventTarget OscillatorNode
instance IsGObject OscillatorNode where
  typeGType :: OscillatorNode -> JSM GType
typeGType OscillatorNode
_ = JSM GType
gTypeOscillatorNode
  {-# INLINE typeGType #-}

noOscillatorNode :: Maybe OscillatorNode
noOscillatorNode :: Maybe OscillatorNode
noOscillatorNode = Maybe OscillatorNode
forall a. Maybe a
Nothing
{-# INLINE noOscillatorNode #-}

gTypeOscillatorNode :: JSM GType
gTypeOscillatorNode :: JSM GType
gTypeOscillatorNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OscillatorNode"

-- | Functions for this inteface are in "JSDOM.OverconstrainedError".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OverconstrainedError Mozilla OverconstrainedError documentation>
newtype OverconstrainedError = OverconstrainedError { OverconstrainedError -> JSVal
unOverconstrainedError :: JSVal }

instance PToJSVal OverconstrainedError where
  pToJSVal :: OverconstrainedError -> JSVal
pToJSVal = OverconstrainedError -> JSVal
unOverconstrainedError
  {-# INLINE pToJSVal #-}

instance PFromJSVal OverconstrainedError where
  pFromJSVal :: JSVal -> OverconstrainedError
pFromJSVal = JSVal -> OverconstrainedError
OverconstrainedError
  {-# INLINE pFromJSVal #-}

instance ToJSVal OverconstrainedError where
  toJSVal :: OverconstrainedError -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OverconstrainedError -> JSVal)
-> OverconstrainedError
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OverconstrainedError -> JSVal
unOverconstrainedError
  {-# INLINE toJSVal #-}

instance FromJSVal OverconstrainedError where
  fromJSVal :: JSVal -> JSM (Maybe OverconstrainedError)
fromJSVal JSVal
v = (JSVal -> OverconstrainedError)
-> Maybe JSVal -> Maybe OverconstrainedError
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OverconstrainedError
OverconstrainedError (Maybe JSVal -> Maybe OverconstrainedError)
-> JSM (Maybe JSVal) -> JSM (Maybe OverconstrainedError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OverconstrainedError
fromJSValUnchecked = OverconstrainedError -> JSM OverconstrainedError
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OverconstrainedError -> JSM OverconstrainedError)
-> (JSVal -> OverconstrainedError)
-> JSVal
-> JSM OverconstrainedError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OverconstrainedError
OverconstrainedError
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OverconstrainedError where
  makeObject :: OverconstrainedError -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OverconstrainedError -> JSVal)
-> OverconstrainedError
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OverconstrainedError -> JSVal
unOverconstrainedError

instance IsGObject OverconstrainedError where
  typeGType :: OverconstrainedError -> JSM GType
typeGType OverconstrainedError
_ = JSM GType
gTypeOverconstrainedError
  {-# INLINE typeGType #-}

noOverconstrainedError :: Maybe OverconstrainedError
noOverconstrainedError :: Maybe OverconstrainedError
noOverconstrainedError = Maybe OverconstrainedError
forall a. Maybe a
Nothing
{-# INLINE noOverconstrainedError #-}

gTypeOverconstrainedError :: JSM GType
gTypeOverconstrainedError :: JSM GType
gTypeOverconstrainedError = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OverconstrainedError"

-- | Functions for this inteface are in "JSDOM.OverconstrainedErrorEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OverconstrainedErrorEvent Mozilla OverconstrainedErrorEvent documentation>
newtype OverconstrainedErrorEvent = OverconstrainedErrorEvent { OverconstrainedErrorEvent -> JSVal
unOverconstrainedErrorEvent :: JSVal }

instance PToJSVal OverconstrainedErrorEvent where
  pToJSVal :: OverconstrainedErrorEvent -> JSVal
pToJSVal = OverconstrainedErrorEvent -> JSVal
unOverconstrainedErrorEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal OverconstrainedErrorEvent where
  pFromJSVal :: JSVal -> OverconstrainedErrorEvent
pFromJSVal = JSVal -> OverconstrainedErrorEvent
OverconstrainedErrorEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal OverconstrainedErrorEvent where
  toJSVal :: OverconstrainedErrorEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OverconstrainedErrorEvent -> JSVal)
-> OverconstrainedErrorEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OverconstrainedErrorEvent -> JSVal
unOverconstrainedErrorEvent
  {-# INLINE toJSVal #-}

instance FromJSVal OverconstrainedErrorEvent where
  fromJSVal :: JSVal -> JSM (Maybe OverconstrainedErrorEvent)
fromJSVal JSVal
v = (JSVal -> OverconstrainedErrorEvent)
-> Maybe JSVal -> Maybe OverconstrainedErrorEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OverconstrainedErrorEvent
OverconstrainedErrorEvent (Maybe JSVal -> Maybe OverconstrainedErrorEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe OverconstrainedErrorEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OverconstrainedErrorEvent
fromJSValUnchecked = OverconstrainedErrorEvent -> JSM OverconstrainedErrorEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OverconstrainedErrorEvent -> JSM OverconstrainedErrorEvent)
-> (JSVal -> OverconstrainedErrorEvent)
-> JSVal
-> JSM OverconstrainedErrorEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OverconstrainedErrorEvent
OverconstrainedErrorEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OverconstrainedErrorEvent where
  makeObject :: OverconstrainedErrorEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OverconstrainedErrorEvent -> JSVal)
-> OverconstrainedErrorEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OverconstrainedErrorEvent -> JSVal
unOverconstrainedErrorEvent

instance IsEvent OverconstrainedErrorEvent
instance IsGObject OverconstrainedErrorEvent where
  typeGType :: OverconstrainedErrorEvent -> JSM GType
typeGType OverconstrainedErrorEvent
_ = JSM GType
gTypeOverconstrainedErrorEvent
  {-# INLINE typeGType #-}

noOverconstrainedErrorEvent :: Maybe OverconstrainedErrorEvent
noOverconstrainedErrorEvent :: Maybe OverconstrainedErrorEvent
noOverconstrainedErrorEvent = Maybe OverconstrainedErrorEvent
forall a. Maybe a
Nothing
{-# INLINE noOverconstrainedErrorEvent #-}

gTypeOverconstrainedErrorEvent :: JSM GType
gTypeOverconstrainedErrorEvent :: JSM GType
gTypeOverconstrainedErrorEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OverconstrainedErrorEvent"

-- | Functions for this inteface are in "JSDOM.OverconstrainedErrorEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OverconstrainedErrorEventInit Mozilla OverconstrainedErrorEventInit documentation>
newtype OverconstrainedErrorEventInit = OverconstrainedErrorEventInit { OverconstrainedErrorEventInit -> JSVal
unOverconstrainedErrorEventInit :: JSVal }

instance PToJSVal OverconstrainedErrorEventInit where
  pToJSVal :: OverconstrainedErrorEventInit -> JSVal
pToJSVal = OverconstrainedErrorEventInit -> JSVal
unOverconstrainedErrorEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal OverconstrainedErrorEventInit where
  pFromJSVal :: JSVal -> OverconstrainedErrorEventInit
pFromJSVal = JSVal -> OverconstrainedErrorEventInit
OverconstrainedErrorEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal OverconstrainedErrorEventInit where
  toJSVal :: OverconstrainedErrorEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OverconstrainedErrorEventInit -> JSVal)
-> OverconstrainedErrorEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OverconstrainedErrorEventInit -> JSVal
unOverconstrainedErrorEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal OverconstrainedErrorEventInit where
  fromJSVal :: JSVal -> JSM (Maybe OverconstrainedErrorEventInit)
fromJSVal JSVal
v = (JSVal -> OverconstrainedErrorEventInit)
-> Maybe JSVal -> Maybe OverconstrainedErrorEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OverconstrainedErrorEventInit
OverconstrainedErrorEventInit (Maybe JSVal -> Maybe OverconstrainedErrorEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe OverconstrainedErrorEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OverconstrainedErrorEventInit
fromJSValUnchecked = OverconstrainedErrorEventInit -> JSM OverconstrainedErrorEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OverconstrainedErrorEventInit
 -> JSM OverconstrainedErrorEventInit)
-> (JSVal -> OverconstrainedErrorEventInit)
-> JSVal
-> JSM OverconstrainedErrorEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OverconstrainedErrorEventInit
OverconstrainedErrorEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OverconstrainedErrorEventInit where
  makeObject :: OverconstrainedErrorEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OverconstrainedErrorEventInit -> JSVal)
-> OverconstrainedErrorEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OverconstrainedErrorEventInit -> JSVal
unOverconstrainedErrorEventInit

instance IsEventInit OverconstrainedErrorEventInit
instance IsGObject OverconstrainedErrorEventInit where
  typeGType :: OverconstrainedErrorEventInit -> JSM GType
typeGType OverconstrainedErrorEventInit
_ = JSM GType
gTypeOverconstrainedErrorEventInit
  {-# INLINE typeGType #-}

noOverconstrainedErrorEventInit :: Maybe OverconstrainedErrorEventInit
noOverconstrainedErrorEventInit :: Maybe OverconstrainedErrorEventInit
noOverconstrainedErrorEventInit = Maybe OverconstrainedErrorEventInit
forall a. Maybe a
Nothing
{-# INLINE noOverconstrainedErrorEventInit #-}

gTypeOverconstrainedErrorEventInit :: JSM GType
gTypeOverconstrainedErrorEventInit :: JSM GType
gTypeOverconstrainedErrorEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OverconstrainedErrorEventInit"

-- | Functions for this inteface are in "JSDOM.OverflowEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OverflowEvent Mozilla OverflowEvent documentation>
newtype OverflowEvent = OverflowEvent { OverflowEvent -> JSVal
unOverflowEvent :: JSVal }

instance PToJSVal OverflowEvent where
  pToJSVal :: OverflowEvent -> JSVal
pToJSVal = OverflowEvent -> JSVal
unOverflowEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal OverflowEvent where
  pFromJSVal :: JSVal -> OverflowEvent
pFromJSVal = JSVal -> OverflowEvent
OverflowEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal OverflowEvent where
  toJSVal :: OverflowEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OverflowEvent -> JSVal) -> OverflowEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OverflowEvent -> JSVal
unOverflowEvent
  {-# INLINE toJSVal #-}

instance FromJSVal OverflowEvent where
  fromJSVal :: JSVal -> JSM (Maybe OverflowEvent)
fromJSVal JSVal
v = (JSVal -> OverflowEvent) -> Maybe JSVal -> Maybe OverflowEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OverflowEvent
OverflowEvent (Maybe JSVal -> Maybe OverflowEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe OverflowEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OverflowEvent
fromJSValUnchecked = OverflowEvent -> JSM OverflowEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OverflowEvent -> JSM OverflowEvent)
-> (JSVal -> OverflowEvent) -> JSVal -> JSM OverflowEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OverflowEvent
OverflowEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OverflowEvent where
  makeObject :: OverflowEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OverflowEvent -> JSVal) -> OverflowEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OverflowEvent -> JSVal
unOverflowEvent

instance IsEvent OverflowEvent
instance IsGObject OverflowEvent where
  typeGType :: OverflowEvent -> JSM GType
typeGType OverflowEvent
_ = JSM GType
gTypeOverflowEvent
  {-# INLINE typeGType #-}

noOverflowEvent :: Maybe OverflowEvent
noOverflowEvent :: Maybe OverflowEvent
noOverflowEvent = Maybe OverflowEvent
forall a. Maybe a
Nothing
{-# INLINE noOverflowEvent #-}

gTypeOverflowEvent :: JSM GType
gTypeOverflowEvent :: JSM GType
gTypeOverflowEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OverflowEvent"

-- | Functions for this inteface are in "JSDOM.OverflowEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/OverflowEventInit Mozilla OverflowEventInit documentation>
newtype OverflowEventInit = OverflowEventInit { OverflowEventInit -> JSVal
unOverflowEventInit :: JSVal }

instance PToJSVal OverflowEventInit where
  pToJSVal :: OverflowEventInit -> JSVal
pToJSVal = OverflowEventInit -> JSVal
unOverflowEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal OverflowEventInit where
  pFromJSVal :: JSVal -> OverflowEventInit
pFromJSVal = JSVal -> OverflowEventInit
OverflowEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal OverflowEventInit where
  toJSVal :: OverflowEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (OverflowEventInit -> JSVal) -> OverflowEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OverflowEventInit -> JSVal
unOverflowEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal OverflowEventInit where
  fromJSVal :: JSVal -> JSM (Maybe OverflowEventInit)
fromJSVal JSVal
v = (JSVal -> OverflowEventInit)
-> Maybe JSVal -> Maybe OverflowEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> OverflowEventInit
OverflowEventInit (Maybe JSVal -> Maybe OverflowEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe OverflowEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM OverflowEventInit
fromJSValUnchecked = OverflowEventInit -> JSM OverflowEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (OverflowEventInit -> JSM OverflowEventInit)
-> (JSVal -> OverflowEventInit) -> JSVal -> JSM OverflowEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> OverflowEventInit
OverflowEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject OverflowEventInit where
  makeObject :: OverflowEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (OverflowEventInit -> JSVal) -> OverflowEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OverflowEventInit -> JSVal
unOverflowEventInit

instance IsEventInit OverflowEventInit
instance IsGObject OverflowEventInit where
  typeGType :: OverflowEventInit -> JSM GType
typeGType OverflowEventInit
_ = JSM GType
gTypeOverflowEventInit
  {-# INLINE typeGType #-}

noOverflowEventInit :: Maybe OverflowEventInit
noOverflowEventInit :: Maybe OverflowEventInit
noOverflowEventInit = Maybe OverflowEventInit
forall a. Maybe a
Nothing
{-# INLINE noOverflowEventInit #-}

gTypeOverflowEventInit :: JSM GType
gTypeOverflowEventInit :: JSM GType
gTypeOverflowEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"OverflowEventInit"

-- | Functions for this inteface are in "JSDOM.PageTransitionEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PageTransitionEvent Mozilla PageTransitionEvent documentation>
newtype PageTransitionEvent = PageTransitionEvent { PageTransitionEvent -> JSVal
unPageTransitionEvent :: JSVal }

instance PToJSVal PageTransitionEvent where
  pToJSVal :: PageTransitionEvent -> JSVal
pToJSVal = PageTransitionEvent -> JSVal
unPageTransitionEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal PageTransitionEvent where
  pFromJSVal :: JSVal -> PageTransitionEvent
pFromJSVal = JSVal -> PageTransitionEvent
PageTransitionEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal PageTransitionEvent where
  toJSVal :: PageTransitionEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PageTransitionEvent -> JSVal)
-> PageTransitionEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageTransitionEvent -> JSVal
unPageTransitionEvent
  {-# INLINE toJSVal #-}

instance FromJSVal PageTransitionEvent where
  fromJSVal :: JSVal -> JSM (Maybe PageTransitionEvent)
fromJSVal JSVal
v = (JSVal -> PageTransitionEvent)
-> Maybe JSVal -> Maybe PageTransitionEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PageTransitionEvent
PageTransitionEvent (Maybe JSVal -> Maybe PageTransitionEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe PageTransitionEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PageTransitionEvent
fromJSValUnchecked = PageTransitionEvent -> JSM PageTransitionEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PageTransitionEvent -> JSM PageTransitionEvent)
-> (JSVal -> PageTransitionEvent)
-> JSVal
-> JSM PageTransitionEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PageTransitionEvent
PageTransitionEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PageTransitionEvent where
  makeObject :: PageTransitionEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PageTransitionEvent -> JSVal)
-> PageTransitionEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageTransitionEvent -> JSVal
unPageTransitionEvent

instance IsEvent PageTransitionEvent
instance IsGObject PageTransitionEvent where
  typeGType :: PageTransitionEvent -> JSM GType
typeGType PageTransitionEvent
_ = JSM GType
gTypePageTransitionEvent
  {-# INLINE typeGType #-}

noPageTransitionEvent :: Maybe PageTransitionEvent
noPageTransitionEvent :: Maybe PageTransitionEvent
noPageTransitionEvent = Maybe PageTransitionEvent
forall a. Maybe a
Nothing
{-# INLINE noPageTransitionEvent #-}

gTypePageTransitionEvent :: JSM GType
gTypePageTransitionEvent :: JSM GType
gTypePageTransitionEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PageTransitionEvent"

-- | Functions for this inteface are in "JSDOM.PageTransitionEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PageTransitionEventInit Mozilla PageTransitionEventInit documentation>
newtype PageTransitionEventInit = PageTransitionEventInit { PageTransitionEventInit -> JSVal
unPageTransitionEventInit :: JSVal }

instance PToJSVal PageTransitionEventInit where
  pToJSVal :: PageTransitionEventInit -> JSVal
pToJSVal = PageTransitionEventInit -> JSVal
unPageTransitionEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal PageTransitionEventInit where
  pFromJSVal :: JSVal -> PageTransitionEventInit
pFromJSVal = JSVal -> PageTransitionEventInit
PageTransitionEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal PageTransitionEventInit where
  toJSVal :: PageTransitionEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PageTransitionEventInit -> JSVal)
-> PageTransitionEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageTransitionEventInit -> JSVal
unPageTransitionEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal PageTransitionEventInit where
  fromJSVal :: JSVal -> JSM (Maybe PageTransitionEventInit)
fromJSVal JSVal
v = (JSVal -> PageTransitionEventInit)
-> Maybe JSVal -> Maybe PageTransitionEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PageTransitionEventInit
PageTransitionEventInit (Maybe JSVal -> Maybe PageTransitionEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe PageTransitionEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PageTransitionEventInit
fromJSValUnchecked = PageTransitionEventInit -> JSM PageTransitionEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PageTransitionEventInit -> JSM PageTransitionEventInit)
-> (JSVal -> PageTransitionEventInit)
-> JSVal
-> JSM PageTransitionEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PageTransitionEventInit
PageTransitionEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PageTransitionEventInit where
  makeObject :: PageTransitionEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PageTransitionEventInit -> JSVal)
-> PageTransitionEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageTransitionEventInit -> JSVal
unPageTransitionEventInit

instance IsEventInit PageTransitionEventInit
instance IsGObject PageTransitionEventInit where
  typeGType :: PageTransitionEventInit -> JSM GType
typeGType PageTransitionEventInit
_ = JSM GType
gTypePageTransitionEventInit
  {-# INLINE typeGType #-}

noPageTransitionEventInit :: Maybe PageTransitionEventInit
noPageTransitionEventInit :: Maybe PageTransitionEventInit
noPageTransitionEventInit = Maybe PageTransitionEventInit
forall a. Maybe a
Nothing
{-# INLINE noPageTransitionEventInit #-}

gTypePageTransitionEventInit :: JSM GType
gTypePageTransitionEventInit :: JSM GType
gTypePageTransitionEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PageTransitionEventInit"

-- | Functions for this inteface are in "JSDOM.PannerNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/webkitAudioPannerNode Mozilla webkitAudioPannerNode documentation>
newtype PannerNode = PannerNode { PannerNode -> JSVal
unPannerNode :: JSVal }

instance PToJSVal PannerNode where
  pToJSVal :: PannerNode -> JSVal
pToJSVal = PannerNode -> JSVal
unPannerNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal PannerNode where
  pFromJSVal :: JSVal -> PannerNode
pFromJSVal = JSVal -> PannerNode
PannerNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal PannerNode where
  toJSVal :: PannerNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PannerNode -> JSVal) -> PannerNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PannerNode -> JSVal
unPannerNode
  {-# INLINE toJSVal #-}

instance FromJSVal PannerNode where
  fromJSVal :: JSVal -> JSM (Maybe PannerNode)
fromJSVal JSVal
v = (JSVal -> PannerNode) -> Maybe JSVal -> Maybe PannerNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PannerNode
PannerNode (Maybe JSVal -> Maybe PannerNode)
-> JSM (Maybe JSVal) -> JSM (Maybe PannerNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PannerNode
fromJSValUnchecked = PannerNode -> JSM PannerNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PannerNode -> JSM PannerNode)
-> (JSVal -> PannerNode) -> JSVal -> JSM PannerNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PannerNode
PannerNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PannerNode where
  makeObject :: PannerNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PannerNode -> JSVal) -> PannerNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PannerNode -> JSVal
unPannerNode

instance IsAudioNode PannerNode
instance IsEventTarget PannerNode
instance IsGObject PannerNode where
  typeGType :: PannerNode -> JSM GType
typeGType PannerNode
_ = JSM GType
gTypePannerNode
  {-# INLINE typeGType #-}

noPannerNode :: Maybe PannerNode
noPannerNode :: Maybe PannerNode
noPannerNode = Maybe PannerNode
forall a. Maybe a
Nothing
{-# INLINE noPannerNode #-}

gTypePannerNode :: JSM GType
gTypePannerNode :: JSM GType
gTypePannerNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"webkitAudioPannerNode"

-- | Functions for this inteface are in "JSDOM.ParentNode".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ParentNode Mozilla ParentNode documentation>
newtype ParentNode = ParentNode { ParentNode -> JSVal
unParentNode :: JSVal }

instance PToJSVal ParentNode where
  pToJSVal :: ParentNode -> JSVal
pToJSVal = ParentNode -> JSVal
unParentNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal ParentNode where
  pFromJSVal :: JSVal -> ParentNode
pFromJSVal = JSVal -> ParentNode
ParentNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal ParentNode where
  toJSVal :: ParentNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ParentNode -> JSVal) -> ParentNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParentNode -> JSVal
unParentNode
  {-# INLINE toJSVal #-}

instance FromJSVal ParentNode where
  fromJSVal :: JSVal -> JSM (Maybe ParentNode)
fromJSVal JSVal
v = (JSVal -> ParentNode) -> Maybe JSVal -> Maybe ParentNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ParentNode
ParentNode (Maybe JSVal -> Maybe ParentNode)
-> JSM (Maybe JSVal) -> JSM (Maybe ParentNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ParentNode
fromJSValUnchecked = ParentNode -> JSM ParentNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ParentNode -> JSM ParentNode)
-> (JSVal -> ParentNode) -> JSVal -> JSM ParentNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ParentNode
ParentNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ParentNode where
  makeObject :: ParentNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ParentNode -> JSVal) -> ParentNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParentNode -> JSVal
unParentNode

class (IsGObject o) => IsParentNode o
toParentNode :: IsParentNode o => o -> ParentNode
toParentNode :: forall o. IsParentNode o => o -> ParentNode
toParentNode = JSVal -> ParentNode
ParentNode (JSVal -> ParentNode) -> (o -> JSVal) -> o -> ParentNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsParentNode ParentNode
instance IsGObject ParentNode where
  typeGType :: ParentNode -> JSM GType
typeGType ParentNode
_ = JSM GType
gTypeParentNode
  {-# INLINE typeGType #-}

noParentNode :: Maybe ParentNode
noParentNode :: Maybe ParentNode
noParentNode = Maybe ParentNode
forall a. Maybe a
Nothing
{-# INLINE noParentNode #-}

gTypeParentNode :: JSM GType
gTypeParentNode :: JSM GType
gTypeParentNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ParentNode"

-- | Functions for this inteface are in "JSDOM.PasswordCredential".
-- Base interface functions are in:
--
--     * "JSDOM.SiteBoundCredential"
--     * "JSDOM.BasicCredential"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PasswordCredential Mozilla PasswordCredential documentation>
newtype PasswordCredential = PasswordCredential { PasswordCredential -> JSVal
unPasswordCredential :: JSVal }

instance PToJSVal PasswordCredential where
  pToJSVal :: PasswordCredential -> JSVal
pToJSVal = PasswordCredential -> JSVal
unPasswordCredential
  {-# INLINE pToJSVal #-}

instance PFromJSVal PasswordCredential where
  pFromJSVal :: JSVal -> PasswordCredential
pFromJSVal = JSVal -> PasswordCredential
PasswordCredential
  {-# INLINE pFromJSVal #-}

instance ToJSVal PasswordCredential where
  toJSVal :: PasswordCredential -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PasswordCredential -> JSVal) -> PasswordCredential -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PasswordCredential -> JSVal
unPasswordCredential
  {-# INLINE toJSVal #-}

instance FromJSVal PasswordCredential where
  fromJSVal :: JSVal -> JSM (Maybe PasswordCredential)
fromJSVal JSVal
v = (JSVal -> PasswordCredential)
-> Maybe JSVal -> Maybe PasswordCredential
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PasswordCredential
PasswordCredential (Maybe JSVal -> Maybe PasswordCredential)
-> JSM (Maybe JSVal) -> JSM (Maybe PasswordCredential)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PasswordCredential
fromJSValUnchecked = PasswordCredential -> JSM PasswordCredential
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PasswordCredential -> JSM PasswordCredential)
-> (JSVal -> PasswordCredential) -> JSVal -> JSM PasswordCredential
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PasswordCredential
PasswordCredential
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PasswordCredential where
  makeObject :: PasswordCredential -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PasswordCredential -> JSVal)
-> PasswordCredential
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PasswordCredential -> JSVal
unPasswordCredential

instance IsSiteBoundCredential PasswordCredential
instance IsBasicCredential PasswordCredential
instance IsGObject PasswordCredential where
  typeGType :: PasswordCredential -> JSM GType
typeGType PasswordCredential
_ = JSM GType
gTypePasswordCredential
  {-# INLINE typeGType #-}

noPasswordCredential :: Maybe PasswordCredential
noPasswordCredential :: Maybe PasswordCredential
noPasswordCredential = Maybe PasswordCredential
forall a. Maybe a
Nothing
{-# INLINE noPasswordCredential #-}

gTypePasswordCredential :: JSM GType
gTypePasswordCredential :: JSM GType
gTypePasswordCredential = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PasswordCredential"

-- | Functions for this inteface are in "JSDOM.PasswordCredentialData".
-- Base interface functions are in:
--
--     * "JSDOM.SiteBoundCredentialData"
--     * "JSDOM.CredentialData"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PasswordCredentialData Mozilla PasswordCredentialData documentation>
newtype PasswordCredentialData = PasswordCredentialData { PasswordCredentialData -> JSVal
unPasswordCredentialData :: JSVal }

instance PToJSVal PasswordCredentialData where
  pToJSVal :: PasswordCredentialData -> JSVal
pToJSVal = PasswordCredentialData -> JSVal
unPasswordCredentialData
  {-# INLINE pToJSVal #-}

instance PFromJSVal PasswordCredentialData where
  pFromJSVal :: JSVal -> PasswordCredentialData
pFromJSVal = JSVal -> PasswordCredentialData
PasswordCredentialData
  {-# INLINE pFromJSVal #-}

instance ToJSVal PasswordCredentialData where
  toJSVal :: PasswordCredentialData -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PasswordCredentialData -> JSVal)
-> PasswordCredentialData
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PasswordCredentialData -> JSVal
unPasswordCredentialData
  {-# INLINE toJSVal #-}

instance FromJSVal PasswordCredentialData where
  fromJSVal :: JSVal -> JSM (Maybe PasswordCredentialData)
fromJSVal JSVal
v = (JSVal -> PasswordCredentialData)
-> Maybe JSVal -> Maybe PasswordCredentialData
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PasswordCredentialData
PasswordCredentialData (Maybe JSVal -> Maybe PasswordCredentialData)
-> JSM (Maybe JSVal) -> JSM (Maybe PasswordCredentialData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PasswordCredentialData
fromJSValUnchecked = PasswordCredentialData -> JSM PasswordCredentialData
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PasswordCredentialData -> JSM PasswordCredentialData)
-> (JSVal -> PasswordCredentialData)
-> JSVal
-> JSM PasswordCredentialData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PasswordCredentialData
PasswordCredentialData
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PasswordCredentialData where
  makeObject :: PasswordCredentialData -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PasswordCredentialData -> JSVal)
-> PasswordCredentialData
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PasswordCredentialData -> JSVal
unPasswordCredentialData

instance IsSiteBoundCredentialData PasswordCredentialData
instance IsCredentialData PasswordCredentialData
instance IsGObject PasswordCredentialData where
  typeGType :: PasswordCredentialData -> JSM GType
typeGType PasswordCredentialData
_ = JSM GType
gTypePasswordCredentialData
  {-# INLINE typeGType #-}

noPasswordCredentialData :: Maybe PasswordCredentialData
noPasswordCredentialData :: Maybe PasswordCredentialData
noPasswordCredentialData = Maybe PasswordCredentialData
forall a. Maybe a
Nothing
{-# INLINE noPasswordCredentialData #-}

gTypePasswordCredentialData :: JSM GType
gTypePasswordCredentialData :: JSM GType
gTypePasswordCredentialData = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PasswordCredentialData"

-- | Functions for this inteface are in "JSDOM.Path2D".
-- Base interface functions are in:
--
--     * "JSDOM.CanvasPath"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Path2D Mozilla Path2D documentation>
newtype Path2D = Path2D { Path2D -> JSVal
unPath2D :: JSVal }

instance PToJSVal Path2D where
  pToJSVal :: Path2D -> JSVal
pToJSVal = Path2D -> JSVal
unPath2D
  {-# INLINE pToJSVal #-}

instance PFromJSVal Path2D where
  pFromJSVal :: JSVal -> Path2D
pFromJSVal = JSVal -> Path2D
Path2D
  {-# INLINE pFromJSVal #-}

instance ToJSVal Path2D where
  toJSVal :: Path2D -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Path2D -> JSVal) -> Path2D -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path2D -> JSVal
unPath2D
  {-# INLINE toJSVal #-}

instance FromJSVal Path2D where
  fromJSVal :: JSVal -> JSM (Maybe Path2D)
fromJSVal JSVal
v = (JSVal -> Path2D) -> Maybe JSVal -> Maybe Path2D
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Path2D
Path2D (Maybe JSVal -> Maybe Path2D)
-> JSM (Maybe JSVal) -> JSM (Maybe Path2D)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Path2D
fromJSValUnchecked = Path2D -> JSM Path2D
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Path2D -> JSM Path2D) -> (JSVal -> Path2D) -> JSVal -> JSM Path2D
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Path2D
Path2D
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Path2D where
  makeObject :: Path2D -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Path2D -> JSVal) -> Path2D -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path2D -> JSVal
unPath2D

instance IsCanvasPath Path2D
instance IsGObject Path2D where
  typeGType :: Path2D -> JSM GType
typeGType Path2D
_ = JSM GType
gTypePath2D
  {-# INLINE typeGType #-}

noPath2D :: Maybe Path2D
noPath2D :: Maybe Path2D
noPath2D = Maybe Path2D
forall a. Maybe a
Nothing
{-# INLINE noPath2D #-}

gTypePath2D :: JSM GType
gTypePath2D :: JSM GType
gTypePath2D = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Path2D"

-- | Functions for this inteface are in "JSDOM.Pbkdf2Params".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Pbkdf2Params Mozilla Pbkdf2Params documentation>
newtype Pbkdf2Params = Pbkdf2Params { Pbkdf2Params -> JSVal
unPbkdf2Params :: JSVal }

instance PToJSVal Pbkdf2Params where
  pToJSVal :: Pbkdf2Params -> JSVal
pToJSVal = Pbkdf2Params -> JSVal
unPbkdf2Params
  {-# INLINE pToJSVal #-}

instance PFromJSVal Pbkdf2Params where
  pFromJSVal :: JSVal -> Pbkdf2Params
pFromJSVal = JSVal -> Pbkdf2Params
Pbkdf2Params
  {-# INLINE pFromJSVal #-}

instance ToJSVal Pbkdf2Params where
  toJSVal :: Pbkdf2Params -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Pbkdf2Params -> JSVal) -> Pbkdf2Params -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pbkdf2Params -> JSVal
unPbkdf2Params
  {-# INLINE toJSVal #-}

instance FromJSVal Pbkdf2Params where
  fromJSVal :: JSVal -> JSM (Maybe Pbkdf2Params)
fromJSVal JSVal
v = (JSVal -> Pbkdf2Params) -> Maybe JSVal -> Maybe Pbkdf2Params
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Pbkdf2Params
Pbkdf2Params (Maybe JSVal -> Maybe Pbkdf2Params)
-> JSM (Maybe JSVal) -> JSM (Maybe Pbkdf2Params)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Pbkdf2Params
fromJSValUnchecked = Pbkdf2Params -> JSM Pbkdf2Params
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pbkdf2Params -> JSM Pbkdf2Params)
-> (JSVal -> Pbkdf2Params) -> JSVal -> JSM Pbkdf2Params
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Pbkdf2Params
Pbkdf2Params
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Pbkdf2Params where
  makeObject :: Pbkdf2Params -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Pbkdf2Params -> JSVal) -> Pbkdf2Params -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pbkdf2Params -> JSVal
unPbkdf2Params

instance IsCryptoAlgorithmParameters Pbkdf2Params
instance IsGObject Pbkdf2Params where
  typeGType :: Pbkdf2Params -> JSM GType
typeGType Pbkdf2Params
_ = JSM GType
gTypePbkdf2Params
  {-# INLINE typeGType #-}

noPbkdf2Params :: Maybe Pbkdf2Params
noPbkdf2Params :: Maybe Pbkdf2Params
noPbkdf2Params = Maybe Pbkdf2Params
forall a. Maybe a
Nothing
{-# INLINE noPbkdf2Params #-}

gTypePbkdf2Params :: JSM GType
gTypePbkdf2Params :: JSM GType
gTypePbkdf2Params = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Pbkdf2Params"

-- | Functions for this inteface are in "JSDOM.Performance".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Performance Mozilla Performance documentation>
newtype Performance = Performance { Performance -> JSVal
unPerformance :: JSVal }

instance PToJSVal Performance where
  pToJSVal :: Performance -> JSVal
pToJSVal = Performance -> JSVal
unPerformance
  {-# INLINE pToJSVal #-}

instance PFromJSVal Performance where
  pFromJSVal :: JSVal -> Performance
pFromJSVal = JSVal -> Performance
Performance
  {-# INLINE pFromJSVal #-}

instance ToJSVal Performance where
  toJSVal :: Performance -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Performance -> JSVal) -> Performance -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Performance -> JSVal
unPerformance
  {-# INLINE toJSVal #-}

instance FromJSVal Performance where
  fromJSVal :: JSVal -> JSM (Maybe Performance)
fromJSVal JSVal
v = (JSVal -> Performance) -> Maybe JSVal -> Maybe Performance
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Performance
Performance (Maybe JSVal -> Maybe Performance)
-> JSM (Maybe JSVal) -> JSM (Maybe Performance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Performance
fromJSValUnchecked = Performance -> JSM Performance
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Performance -> JSM Performance)
-> (JSVal -> Performance) -> JSVal -> JSM Performance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Performance
Performance
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Performance where
  makeObject :: Performance -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Performance -> JSVal) -> Performance -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Performance -> JSVal
unPerformance

instance IsEventTarget Performance
instance IsGObject Performance where
  typeGType :: Performance -> JSM GType
typeGType Performance
_ = JSM GType
gTypePerformance
  {-# INLINE typeGType #-}

noPerformance :: Maybe Performance
noPerformance :: Maybe Performance
noPerformance = Maybe Performance
forall a. Maybe a
Nothing
{-# INLINE noPerformance #-}

gTypePerformance :: JSM GType
gTypePerformance :: JSM GType
gTypePerformance = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Performance"

-- | Functions for this inteface are in "JSDOM.PerformanceEntry".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PerformanceEntry Mozilla PerformanceEntry documentation>
newtype PerformanceEntry = PerformanceEntry { PerformanceEntry -> JSVal
unPerformanceEntry :: JSVal }

instance PToJSVal PerformanceEntry where
  pToJSVal :: PerformanceEntry -> JSVal
pToJSVal = PerformanceEntry -> JSVal
unPerformanceEntry
  {-# INLINE pToJSVal #-}

instance PFromJSVal PerformanceEntry where
  pFromJSVal :: JSVal -> PerformanceEntry
pFromJSVal = JSVal -> PerformanceEntry
PerformanceEntry
  {-# INLINE pFromJSVal #-}

instance ToJSVal PerformanceEntry where
  toJSVal :: PerformanceEntry -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PerformanceEntry -> JSVal) -> PerformanceEntry -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceEntry -> JSVal
unPerformanceEntry
  {-# INLINE toJSVal #-}

instance FromJSVal PerformanceEntry where
  fromJSVal :: JSVal -> JSM (Maybe PerformanceEntry)
fromJSVal JSVal
v = (JSVal -> PerformanceEntry)
-> Maybe JSVal -> Maybe PerformanceEntry
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PerformanceEntry
PerformanceEntry (Maybe JSVal -> Maybe PerformanceEntry)
-> JSM (Maybe JSVal) -> JSM (Maybe PerformanceEntry)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PerformanceEntry
fromJSValUnchecked = PerformanceEntry -> JSM PerformanceEntry
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PerformanceEntry -> JSM PerformanceEntry)
-> (JSVal -> PerformanceEntry) -> JSVal -> JSM PerformanceEntry
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PerformanceEntry
PerformanceEntry
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PerformanceEntry where
  makeObject :: PerformanceEntry -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PerformanceEntry -> JSVal) -> PerformanceEntry -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceEntry -> JSVal
unPerformanceEntry

class (IsGObject o) => IsPerformanceEntry o
toPerformanceEntry :: IsPerformanceEntry o => o -> PerformanceEntry
toPerformanceEntry :: forall o. IsPerformanceEntry o => o -> PerformanceEntry
toPerformanceEntry = JSVal -> PerformanceEntry
PerformanceEntry (JSVal -> PerformanceEntry)
-> (o -> JSVal) -> o -> PerformanceEntry
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsPerformanceEntry PerformanceEntry
instance IsGObject PerformanceEntry where
  typeGType :: PerformanceEntry -> JSM GType
typeGType PerformanceEntry
_ = JSM GType
gTypePerformanceEntry
  {-# INLINE typeGType #-}

noPerformanceEntry :: Maybe PerformanceEntry
noPerformanceEntry :: Maybe PerformanceEntry
noPerformanceEntry = Maybe PerformanceEntry
forall a. Maybe a
Nothing
{-# INLINE noPerformanceEntry #-}

gTypePerformanceEntry :: JSM GType
gTypePerformanceEntry :: JSM GType
gTypePerformanceEntry = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PerformanceEntry"

-- | Functions for this inteface are in "JSDOM.PerformanceMark".
-- Base interface functions are in:
--
--     * "JSDOM.PerformanceEntry"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PerformanceMark Mozilla PerformanceMark documentation>
newtype PerformanceMark = PerformanceMark { PerformanceMark -> JSVal
unPerformanceMark :: JSVal }

instance PToJSVal PerformanceMark where
  pToJSVal :: PerformanceMark -> JSVal
pToJSVal = PerformanceMark -> JSVal
unPerformanceMark
  {-# INLINE pToJSVal #-}

instance PFromJSVal PerformanceMark where
  pFromJSVal :: JSVal -> PerformanceMark
pFromJSVal = JSVal -> PerformanceMark
PerformanceMark
  {-# INLINE pFromJSVal #-}

instance ToJSVal PerformanceMark where
  toJSVal :: PerformanceMark -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PerformanceMark -> JSVal) -> PerformanceMark -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceMark -> JSVal
unPerformanceMark
  {-# INLINE toJSVal #-}

instance FromJSVal PerformanceMark where
  fromJSVal :: JSVal -> JSM (Maybe PerformanceMark)
fromJSVal JSVal
v = (JSVal -> PerformanceMark) -> Maybe JSVal -> Maybe PerformanceMark
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PerformanceMark
PerformanceMark (Maybe JSVal -> Maybe PerformanceMark)
-> JSM (Maybe JSVal) -> JSM (Maybe PerformanceMark)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PerformanceMark
fromJSValUnchecked = PerformanceMark -> JSM PerformanceMark
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PerformanceMark -> JSM PerformanceMark)
-> (JSVal -> PerformanceMark) -> JSVal -> JSM PerformanceMark
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PerformanceMark
PerformanceMark
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PerformanceMark where
  makeObject :: PerformanceMark -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PerformanceMark -> JSVal) -> PerformanceMark -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceMark -> JSVal
unPerformanceMark

instance IsPerformanceEntry PerformanceMark
instance IsGObject PerformanceMark where
  typeGType :: PerformanceMark -> JSM GType
typeGType PerformanceMark
_ = JSM GType
gTypePerformanceMark
  {-# INLINE typeGType #-}

noPerformanceMark :: Maybe PerformanceMark
noPerformanceMark :: Maybe PerformanceMark
noPerformanceMark = Maybe PerformanceMark
forall a. Maybe a
Nothing
{-# INLINE noPerformanceMark #-}

gTypePerformanceMark :: JSM GType
gTypePerformanceMark :: JSM GType
gTypePerformanceMark = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PerformanceMark"

-- | Functions for this inteface are in "JSDOM.PerformanceMeasure".
-- Base interface functions are in:
--
--     * "JSDOM.PerformanceEntry"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PerformanceMeasure Mozilla PerformanceMeasure documentation>
newtype PerformanceMeasure = PerformanceMeasure { PerformanceMeasure -> JSVal
unPerformanceMeasure :: JSVal }

instance PToJSVal PerformanceMeasure where
  pToJSVal :: PerformanceMeasure -> JSVal
pToJSVal = PerformanceMeasure -> JSVal
unPerformanceMeasure
  {-# INLINE pToJSVal #-}

instance PFromJSVal PerformanceMeasure where
  pFromJSVal :: JSVal -> PerformanceMeasure
pFromJSVal = JSVal -> PerformanceMeasure
PerformanceMeasure
  {-# INLINE pFromJSVal #-}

instance ToJSVal PerformanceMeasure where
  toJSVal :: PerformanceMeasure -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PerformanceMeasure -> JSVal) -> PerformanceMeasure -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceMeasure -> JSVal
unPerformanceMeasure
  {-# INLINE toJSVal #-}

instance FromJSVal PerformanceMeasure where
  fromJSVal :: JSVal -> JSM (Maybe PerformanceMeasure)
fromJSVal JSVal
v = (JSVal -> PerformanceMeasure)
-> Maybe JSVal -> Maybe PerformanceMeasure
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PerformanceMeasure
PerformanceMeasure (Maybe JSVal -> Maybe PerformanceMeasure)
-> JSM (Maybe JSVal) -> JSM (Maybe PerformanceMeasure)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PerformanceMeasure
fromJSValUnchecked = PerformanceMeasure -> JSM PerformanceMeasure
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PerformanceMeasure -> JSM PerformanceMeasure)
-> (JSVal -> PerformanceMeasure) -> JSVal -> JSM PerformanceMeasure
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PerformanceMeasure
PerformanceMeasure
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PerformanceMeasure where
  makeObject :: PerformanceMeasure -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PerformanceMeasure -> JSVal)
-> PerformanceMeasure
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceMeasure -> JSVal
unPerformanceMeasure

instance IsPerformanceEntry PerformanceMeasure
instance IsGObject PerformanceMeasure where
  typeGType :: PerformanceMeasure -> JSM GType
typeGType PerformanceMeasure
_ = JSM GType
gTypePerformanceMeasure
  {-# INLINE typeGType #-}

noPerformanceMeasure :: Maybe PerformanceMeasure
noPerformanceMeasure :: Maybe PerformanceMeasure
noPerformanceMeasure = Maybe PerformanceMeasure
forall a. Maybe a
Nothing
{-# INLINE noPerformanceMeasure #-}

gTypePerformanceMeasure :: JSM GType
gTypePerformanceMeasure :: JSM GType
gTypePerformanceMeasure = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PerformanceMeasure"

-- | Functions for this inteface are in "JSDOM.PerformanceNavigation".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PerformanceNavigation Mozilla PerformanceNavigation documentation>
newtype PerformanceNavigation = PerformanceNavigation { PerformanceNavigation -> JSVal
unPerformanceNavigation :: JSVal }

instance PToJSVal PerformanceNavigation where
  pToJSVal :: PerformanceNavigation -> JSVal
pToJSVal = PerformanceNavigation -> JSVal
unPerformanceNavigation
  {-# INLINE pToJSVal #-}

instance PFromJSVal PerformanceNavigation where
  pFromJSVal :: JSVal -> PerformanceNavigation
pFromJSVal = JSVal -> PerformanceNavigation
PerformanceNavigation
  {-# INLINE pFromJSVal #-}

instance ToJSVal PerformanceNavigation where
  toJSVal :: PerformanceNavigation -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PerformanceNavigation -> JSVal)
-> PerformanceNavigation
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceNavigation -> JSVal
unPerformanceNavigation
  {-# INLINE toJSVal #-}

instance FromJSVal PerformanceNavigation where
  fromJSVal :: JSVal -> JSM (Maybe PerformanceNavigation)
fromJSVal JSVal
v = (JSVal -> PerformanceNavigation)
-> Maybe JSVal -> Maybe PerformanceNavigation
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PerformanceNavigation
PerformanceNavigation (Maybe JSVal -> Maybe PerformanceNavigation)
-> JSM (Maybe JSVal) -> JSM (Maybe PerformanceNavigation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PerformanceNavigation
fromJSValUnchecked = PerformanceNavigation -> JSM PerformanceNavigation
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PerformanceNavigation -> JSM PerformanceNavigation)
-> (JSVal -> PerformanceNavigation)
-> JSVal
-> JSM PerformanceNavigation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PerformanceNavigation
PerformanceNavigation
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PerformanceNavigation where
  makeObject :: PerformanceNavigation -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PerformanceNavigation -> JSVal)
-> PerformanceNavigation
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceNavigation -> JSVal
unPerformanceNavigation

instance IsGObject PerformanceNavigation where
  typeGType :: PerformanceNavigation -> JSM GType
typeGType PerformanceNavigation
_ = JSM GType
gTypePerformanceNavigation
  {-# INLINE typeGType #-}

noPerformanceNavigation :: Maybe PerformanceNavigation
noPerformanceNavigation :: Maybe PerformanceNavigation
noPerformanceNavigation = Maybe PerformanceNavigation
forall a. Maybe a
Nothing
{-# INLINE noPerformanceNavigation #-}

gTypePerformanceNavigation :: JSM GType
gTypePerformanceNavigation :: JSM GType
gTypePerformanceNavigation = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PerformanceNavigation"

-- | Functions for this inteface are in "JSDOM.PerformanceObserver".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PerformanceObserver Mozilla PerformanceObserver documentation>
newtype PerformanceObserver = PerformanceObserver { PerformanceObserver -> JSVal
unPerformanceObserver :: JSVal }

instance PToJSVal PerformanceObserver where
  pToJSVal :: PerformanceObserver -> JSVal
pToJSVal = PerformanceObserver -> JSVal
unPerformanceObserver
  {-# INLINE pToJSVal #-}

instance PFromJSVal PerformanceObserver where
  pFromJSVal :: JSVal -> PerformanceObserver
pFromJSVal = JSVal -> PerformanceObserver
PerformanceObserver
  {-# INLINE pFromJSVal #-}

instance ToJSVal PerformanceObserver where
  toJSVal :: PerformanceObserver -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PerformanceObserver -> JSVal)
-> PerformanceObserver
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceObserver -> JSVal
unPerformanceObserver
  {-# INLINE toJSVal #-}

instance FromJSVal PerformanceObserver where
  fromJSVal :: JSVal -> JSM (Maybe PerformanceObserver)
fromJSVal JSVal
v = (JSVal -> PerformanceObserver)
-> Maybe JSVal -> Maybe PerformanceObserver
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PerformanceObserver
PerformanceObserver (Maybe JSVal -> Maybe PerformanceObserver)
-> JSM (Maybe JSVal) -> JSM (Maybe PerformanceObserver)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PerformanceObserver
fromJSValUnchecked = PerformanceObserver -> JSM PerformanceObserver
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PerformanceObserver -> JSM PerformanceObserver)
-> (JSVal -> PerformanceObserver)
-> JSVal
-> JSM PerformanceObserver
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PerformanceObserver
PerformanceObserver
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PerformanceObserver where
  makeObject :: PerformanceObserver -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PerformanceObserver -> JSVal)
-> PerformanceObserver
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceObserver -> JSVal
unPerformanceObserver

instance IsGObject PerformanceObserver where
  typeGType :: PerformanceObserver -> JSM GType
typeGType PerformanceObserver
_ = JSM GType
gTypePerformanceObserver
  {-# INLINE typeGType #-}

noPerformanceObserver :: Maybe PerformanceObserver
noPerformanceObserver :: Maybe PerformanceObserver
noPerformanceObserver = Maybe PerformanceObserver
forall a. Maybe a
Nothing
{-# INLINE noPerformanceObserver #-}

gTypePerformanceObserver :: JSM GType
gTypePerformanceObserver :: JSM GType
gTypePerformanceObserver = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PerformanceObserver"

-- | Functions for this inteface are in "JSDOM.PerformanceObserverEntryList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PerformanceObserverEntryList Mozilla PerformanceObserverEntryList documentation>
newtype PerformanceObserverEntryList = PerformanceObserverEntryList { PerformanceObserverEntryList -> JSVal
unPerformanceObserverEntryList :: JSVal }

instance PToJSVal PerformanceObserverEntryList where
  pToJSVal :: PerformanceObserverEntryList -> JSVal
pToJSVal = PerformanceObserverEntryList -> JSVal
unPerformanceObserverEntryList
  {-# INLINE pToJSVal #-}

instance PFromJSVal PerformanceObserverEntryList where
  pFromJSVal :: JSVal -> PerformanceObserverEntryList
pFromJSVal = JSVal -> PerformanceObserverEntryList
PerformanceObserverEntryList
  {-# INLINE pFromJSVal #-}

instance ToJSVal PerformanceObserverEntryList where
  toJSVal :: PerformanceObserverEntryList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PerformanceObserverEntryList -> JSVal)
-> PerformanceObserverEntryList
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceObserverEntryList -> JSVal
unPerformanceObserverEntryList
  {-# INLINE toJSVal #-}

instance FromJSVal PerformanceObserverEntryList where
  fromJSVal :: JSVal -> JSM (Maybe PerformanceObserverEntryList)
fromJSVal JSVal
v = (JSVal -> PerformanceObserverEntryList)
-> Maybe JSVal -> Maybe PerformanceObserverEntryList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PerformanceObserverEntryList
PerformanceObserverEntryList (Maybe JSVal -> Maybe PerformanceObserverEntryList)
-> JSM (Maybe JSVal) -> JSM (Maybe PerformanceObserverEntryList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PerformanceObserverEntryList
fromJSValUnchecked = PerformanceObserverEntryList -> JSM PerformanceObserverEntryList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PerformanceObserverEntryList -> JSM PerformanceObserverEntryList)
-> (JSVal -> PerformanceObserverEntryList)
-> JSVal
-> JSM PerformanceObserverEntryList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PerformanceObserverEntryList
PerformanceObserverEntryList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PerformanceObserverEntryList where
  makeObject :: PerformanceObserverEntryList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PerformanceObserverEntryList -> JSVal)
-> PerformanceObserverEntryList
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceObserverEntryList -> JSVal
unPerformanceObserverEntryList

instance IsGObject PerformanceObserverEntryList where
  typeGType :: PerformanceObserverEntryList -> JSM GType
typeGType PerformanceObserverEntryList
_ = JSM GType
gTypePerformanceObserverEntryList
  {-# INLINE typeGType #-}

noPerformanceObserverEntryList :: Maybe PerformanceObserverEntryList
noPerformanceObserverEntryList :: Maybe PerformanceObserverEntryList
noPerformanceObserverEntryList = Maybe PerformanceObserverEntryList
forall a. Maybe a
Nothing
{-# INLINE noPerformanceObserverEntryList #-}

gTypePerformanceObserverEntryList :: JSM GType
gTypePerformanceObserverEntryList :: JSM GType
gTypePerformanceObserverEntryList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PerformanceObserverEntryList"

-- | Functions for this inteface are in "JSDOM.PerformanceObserverInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PerformanceObserverInit Mozilla PerformanceObserverInit documentation>
newtype PerformanceObserverInit = PerformanceObserverInit { PerformanceObserverInit -> JSVal
unPerformanceObserverInit :: JSVal }

instance PToJSVal PerformanceObserverInit where
  pToJSVal :: PerformanceObserverInit -> JSVal
pToJSVal = PerformanceObserverInit -> JSVal
unPerformanceObserverInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal PerformanceObserverInit where
  pFromJSVal :: JSVal -> PerformanceObserverInit
pFromJSVal = JSVal -> PerformanceObserverInit
PerformanceObserverInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal PerformanceObserverInit where
  toJSVal :: PerformanceObserverInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PerformanceObserverInit -> JSVal)
-> PerformanceObserverInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceObserverInit -> JSVal
unPerformanceObserverInit
  {-# INLINE toJSVal #-}

instance FromJSVal PerformanceObserverInit where
  fromJSVal :: JSVal -> JSM (Maybe PerformanceObserverInit)
fromJSVal JSVal
v = (JSVal -> PerformanceObserverInit)
-> Maybe JSVal -> Maybe PerformanceObserverInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PerformanceObserverInit
PerformanceObserverInit (Maybe JSVal -> Maybe PerformanceObserverInit)
-> JSM (Maybe JSVal) -> JSM (Maybe PerformanceObserverInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PerformanceObserverInit
fromJSValUnchecked = PerformanceObserverInit -> JSM PerformanceObserverInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PerformanceObserverInit -> JSM PerformanceObserverInit)
-> (JSVal -> PerformanceObserverInit)
-> JSVal
-> JSM PerformanceObserverInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PerformanceObserverInit
PerformanceObserverInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PerformanceObserverInit where
  makeObject :: PerformanceObserverInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PerformanceObserverInit -> JSVal)
-> PerformanceObserverInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceObserverInit -> JSVal
unPerformanceObserverInit

instance IsGObject PerformanceObserverInit where
  typeGType :: PerformanceObserverInit -> JSM GType
typeGType PerformanceObserverInit
_ = JSM GType
gTypePerformanceObserverInit
  {-# INLINE typeGType #-}

noPerformanceObserverInit :: Maybe PerformanceObserverInit
noPerformanceObserverInit :: Maybe PerformanceObserverInit
noPerformanceObserverInit = Maybe PerformanceObserverInit
forall a. Maybe a
Nothing
{-# INLINE noPerformanceObserverInit #-}

gTypePerformanceObserverInit :: JSM GType
gTypePerformanceObserverInit :: JSM GType
gTypePerformanceObserverInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PerformanceObserverInit"

-- | Functions for this inteface are in "JSDOM.PerformanceResourceTiming".
-- Base interface functions are in:
--
--     * "JSDOM.PerformanceEntry"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PerformanceResourceTiming Mozilla PerformanceResourceTiming documentation>
newtype PerformanceResourceTiming = PerformanceResourceTiming { PerformanceResourceTiming -> JSVal
unPerformanceResourceTiming :: JSVal }

instance PToJSVal PerformanceResourceTiming where
  pToJSVal :: PerformanceResourceTiming -> JSVal
pToJSVal = PerformanceResourceTiming -> JSVal
unPerformanceResourceTiming
  {-# INLINE pToJSVal #-}

instance PFromJSVal PerformanceResourceTiming where
  pFromJSVal :: JSVal -> PerformanceResourceTiming
pFromJSVal = JSVal -> PerformanceResourceTiming
PerformanceResourceTiming
  {-# INLINE pFromJSVal #-}

instance ToJSVal PerformanceResourceTiming where
  toJSVal :: PerformanceResourceTiming -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PerformanceResourceTiming -> JSVal)
-> PerformanceResourceTiming
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceResourceTiming -> JSVal
unPerformanceResourceTiming
  {-# INLINE toJSVal #-}

instance FromJSVal PerformanceResourceTiming where
  fromJSVal :: JSVal -> JSM (Maybe PerformanceResourceTiming)
fromJSVal JSVal
v = (JSVal -> PerformanceResourceTiming)
-> Maybe JSVal -> Maybe PerformanceResourceTiming
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PerformanceResourceTiming
PerformanceResourceTiming (Maybe JSVal -> Maybe PerformanceResourceTiming)
-> JSM (Maybe JSVal) -> JSM (Maybe PerformanceResourceTiming)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PerformanceResourceTiming
fromJSValUnchecked = PerformanceResourceTiming -> JSM PerformanceResourceTiming
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PerformanceResourceTiming -> JSM PerformanceResourceTiming)
-> (JSVal -> PerformanceResourceTiming)
-> JSVal
-> JSM PerformanceResourceTiming
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PerformanceResourceTiming
PerformanceResourceTiming
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PerformanceResourceTiming where
  makeObject :: PerformanceResourceTiming -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PerformanceResourceTiming -> JSVal)
-> PerformanceResourceTiming
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceResourceTiming -> JSVal
unPerformanceResourceTiming

instance IsPerformanceEntry PerformanceResourceTiming
instance IsGObject PerformanceResourceTiming where
  typeGType :: PerformanceResourceTiming -> JSM GType
typeGType PerformanceResourceTiming
_ = JSM GType
gTypePerformanceResourceTiming
  {-# INLINE typeGType #-}

noPerformanceResourceTiming :: Maybe PerformanceResourceTiming
noPerformanceResourceTiming :: Maybe PerformanceResourceTiming
noPerformanceResourceTiming = Maybe PerformanceResourceTiming
forall a. Maybe a
Nothing
{-# INLINE noPerformanceResourceTiming #-}

gTypePerformanceResourceTiming :: JSM GType
gTypePerformanceResourceTiming :: JSM GType
gTypePerformanceResourceTiming = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PerformanceResourceTiming"

-- | Functions for this inteface are in "JSDOM.PerformanceTiming".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PerformanceTiming Mozilla PerformanceTiming documentation>
newtype PerformanceTiming = PerformanceTiming { PerformanceTiming -> JSVal
unPerformanceTiming :: JSVal }

instance PToJSVal PerformanceTiming where
  pToJSVal :: PerformanceTiming -> JSVal
pToJSVal = PerformanceTiming -> JSVal
unPerformanceTiming
  {-# INLINE pToJSVal #-}

instance PFromJSVal PerformanceTiming where
  pFromJSVal :: JSVal -> PerformanceTiming
pFromJSVal = JSVal -> PerformanceTiming
PerformanceTiming
  {-# INLINE pFromJSVal #-}

instance ToJSVal PerformanceTiming where
  toJSVal :: PerformanceTiming -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PerformanceTiming -> JSVal) -> PerformanceTiming -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceTiming -> JSVal
unPerformanceTiming
  {-# INLINE toJSVal #-}

instance FromJSVal PerformanceTiming where
  fromJSVal :: JSVal -> JSM (Maybe PerformanceTiming)
fromJSVal JSVal
v = (JSVal -> PerformanceTiming)
-> Maybe JSVal -> Maybe PerformanceTiming
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PerformanceTiming
PerformanceTiming (Maybe JSVal -> Maybe PerformanceTiming)
-> JSM (Maybe JSVal) -> JSM (Maybe PerformanceTiming)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PerformanceTiming
fromJSValUnchecked = PerformanceTiming -> JSM PerformanceTiming
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PerformanceTiming -> JSM PerformanceTiming)
-> (JSVal -> PerformanceTiming) -> JSVal -> JSM PerformanceTiming
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PerformanceTiming
PerformanceTiming
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PerformanceTiming where
  makeObject :: PerformanceTiming -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PerformanceTiming -> JSVal) -> PerformanceTiming -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceTiming -> JSVal
unPerformanceTiming

instance IsGObject PerformanceTiming where
  typeGType :: PerformanceTiming -> JSM GType
typeGType PerformanceTiming
_ = JSM GType
gTypePerformanceTiming
  {-# INLINE typeGType #-}

noPerformanceTiming :: Maybe PerformanceTiming
noPerformanceTiming :: Maybe PerformanceTiming
noPerformanceTiming = Maybe PerformanceTiming
forall a. Maybe a
Nothing
{-# INLINE noPerformanceTiming #-}

gTypePerformanceTiming :: JSM GType
gTypePerformanceTiming :: JSM GType
gTypePerformanceTiming = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PerformanceTiming"

-- | Functions for this inteface are in "JSDOM.PeriodicWave".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PeriodicWave Mozilla PeriodicWave documentation>
newtype PeriodicWave = PeriodicWave { PeriodicWave -> JSVal
unPeriodicWave :: JSVal }

instance PToJSVal PeriodicWave where
  pToJSVal :: PeriodicWave -> JSVal
pToJSVal = PeriodicWave -> JSVal
unPeriodicWave
  {-# INLINE pToJSVal #-}

instance PFromJSVal PeriodicWave where
  pFromJSVal :: JSVal -> PeriodicWave
pFromJSVal = JSVal -> PeriodicWave
PeriodicWave
  {-# INLINE pFromJSVal #-}

instance ToJSVal PeriodicWave where
  toJSVal :: PeriodicWave -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PeriodicWave -> JSVal) -> PeriodicWave -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PeriodicWave -> JSVal
unPeriodicWave
  {-# INLINE toJSVal #-}

instance FromJSVal PeriodicWave where
  fromJSVal :: JSVal -> JSM (Maybe PeriodicWave)
fromJSVal JSVal
v = (JSVal -> PeriodicWave) -> Maybe JSVal -> Maybe PeriodicWave
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PeriodicWave
PeriodicWave (Maybe JSVal -> Maybe PeriodicWave)
-> JSM (Maybe JSVal) -> JSM (Maybe PeriodicWave)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PeriodicWave
fromJSValUnchecked = PeriodicWave -> JSM PeriodicWave
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PeriodicWave -> JSM PeriodicWave)
-> (JSVal -> PeriodicWave) -> JSVal -> JSM PeriodicWave
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PeriodicWave
PeriodicWave
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PeriodicWave where
  makeObject :: PeriodicWave -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PeriodicWave -> JSVal) -> PeriodicWave -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PeriodicWave -> JSVal
unPeriodicWave

instance IsGObject PeriodicWave where
  typeGType :: PeriodicWave -> JSM GType
typeGType PeriodicWave
_ = JSM GType
gTypePeriodicWave
  {-# INLINE typeGType #-}

noPeriodicWave :: Maybe PeriodicWave
noPeriodicWave :: Maybe PeriodicWave
noPeriodicWave = Maybe PeriodicWave
forall a. Maybe a
Nothing
{-# INLINE noPeriodicWave #-}

gTypePeriodicWave :: JSM GType
gTypePeriodicWave :: JSM GType
gTypePeriodicWave = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PeriodicWave"

-- | Functions for this inteface are in "JSDOM.Plugin".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Plugin Mozilla Plugin documentation>
newtype Plugin = Plugin { Plugin -> JSVal
unPlugin :: JSVal }

instance PToJSVal Plugin where
  pToJSVal :: Plugin -> JSVal
pToJSVal = Plugin -> JSVal
unPlugin
  {-# INLINE pToJSVal #-}

instance PFromJSVal Plugin where
  pFromJSVal :: JSVal -> Plugin
pFromJSVal = JSVal -> Plugin
Plugin
  {-# INLINE pFromJSVal #-}

instance ToJSVal Plugin where
  toJSVal :: Plugin -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Plugin -> JSVal) -> Plugin -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Plugin -> JSVal
unPlugin
  {-# INLINE toJSVal #-}

instance FromJSVal Plugin where
  fromJSVal :: JSVal -> JSM (Maybe Plugin)
fromJSVal JSVal
v = (JSVal -> Plugin) -> Maybe JSVal -> Maybe Plugin
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Plugin
Plugin (Maybe JSVal -> Maybe Plugin)
-> JSM (Maybe JSVal) -> JSM (Maybe Plugin)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Plugin
fromJSValUnchecked = Plugin -> JSM Plugin
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Plugin -> JSM Plugin) -> (JSVal -> Plugin) -> JSVal -> JSM Plugin
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Plugin
Plugin
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Plugin where
  makeObject :: Plugin -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Plugin -> JSVal) -> Plugin -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Plugin -> JSVal
unPlugin

instance IsGObject Plugin where
  typeGType :: Plugin -> JSM GType
typeGType Plugin
_ = JSM GType
gTypePlugin
  {-# INLINE typeGType #-}

noPlugin :: Maybe Plugin
noPlugin :: Maybe Plugin
noPlugin = Maybe Plugin
forall a. Maybe a
Nothing
{-# INLINE noPlugin #-}

gTypePlugin :: JSM GType
gTypePlugin :: JSM GType
gTypePlugin = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Plugin"

-- | Functions for this inteface are in "JSDOM.PluginArray".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PluginArray Mozilla PluginArray documentation>
newtype PluginArray = PluginArray { PluginArray -> JSVal
unPluginArray :: JSVal }

instance PToJSVal PluginArray where
  pToJSVal :: PluginArray -> JSVal
pToJSVal = PluginArray -> JSVal
unPluginArray
  {-# INLINE pToJSVal #-}

instance PFromJSVal PluginArray where
  pFromJSVal :: JSVal -> PluginArray
pFromJSVal = JSVal -> PluginArray
PluginArray
  {-# INLINE pFromJSVal #-}

instance ToJSVal PluginArray where
  toJSVal :: PluginArray -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PluginArray -> JSVal) -> PluginArray -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PluginArray -> JSVal
unPluginArray
  {-# INLINE toJSVal #-}

instance FromJSVal PluginArray where
  fromJSVal :: JSVal -> JSM (Maybe PluginArray)
fromJSVal JSVal
v = (JSVal -> PluginArray) -> Maybe JSVal -> Maybe PluginArray
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PluginArray
PluginArray (Maybe JSVal -> Maybe PluginArray)
-> JSM (Maybe JSVal) -> JSM (Maybe PluginArray)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PluginArray
fromJSValUnchecked = PluginArray -> JSM PluginArray
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PluginArray -> JSM PluginArray)
-> (JSVal -> PluginArray) -> JSVal -> JSM PluginArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PluginArray
PluginArray
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PluginArray where
  makeObject :: PluginArray -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PluginArray -> JSVal) -> PluginArray -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PluginArray -> JSVal
unPluginArray

instance IsGObject PluginArray where
  typeGType :: PluginArray -> JSM GType
typeGType PluginArray
_ = JSM GType
gTypePluginArray
  {-# INLINE typeGType #-}

noPluginArray :: Maybe PluginArray
noPluginArray :: Maybe PluginArray
noPluginArray = Maybe PluginArray
forall a. Maybe a
Nothing
{-# INLINE noPluginArray #-}

gTypePluginArray :: JSM GType
gTypePluginArray :: JSM GType
gTypePluginArray = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PluginArray"

-- | Functions for this inteface are in "JSDOM.PopStateEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PopStateEvent Mozilla PopStateEvent documentation>
newtype PopStateEvent = PopStateEvent { PopStateEvent -> JSVal
unPopStateEvent :: JSVal }

instance PToJSVal PopStateEvent where
  pToJSVal :: PopStateEvent -> JSVal
pToJSVal = PopStateEvent -> JSVal
unPopStateEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal PopStateEvent where
  pFromJSVal :: JSVal -> PopStateEvent
pFromJSVal = JSVal -> PopStateEvent
PopStateEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal PopStateEvent where
  toJSVal :: PopStateEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PopStateEvent -> JSVal) -> PopStateEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PopStateEvent -> JSVal
unPopStateEvent
  {-# INLINE toJSVal #-}

instance FromJSVal PopStateEvent where
  fromJSVal :: JSVal -> JSM (Maybe PopStateEvent)
fromJSVal JSVal
v = (JSVal -> PopStateEvent) -> Maybe JSVal -> Maybe PopStateEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PopStateEvent
PopStateEvent (Maybe JSVal -> Maybe PopStateEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe PopStateEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PopStateEvent
fromJSValUnchecked = PopStateEvent -> JSM PopStateEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PopStateEvent -> JSM PopStateEvent)
-> (JSVal -> PopStateEvent) -> JSVal -> JSM PopStateEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PopStateEvent
PopStateEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PopStateEvent where
  makeObject :: PopStateEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PopStateEvent -> JSVal) -> PopStateEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PopStateEvent -> JSVal
unPopStateEvent

instance IsEvent PopStateEvent
instance IsGObject PopStateEvent where
  typeGType :: PopStateEvent -> JSM GType
typeGType PopStateEvent
_ = JSM GType
gTypePopStateEvent
  {-# INLINE typeGType #-}

noPopStateEvent :: Maybe PopStateEvent
noPopStateEvent :: Maybe PopStateEvent
noPopStateEvent = Maybe PopStateEvent
forall a. Maybe a
Nothing
{-# INLINE noPopStateEvent #-}

gTypePopStateEvent :: JSM GType
gTypePopStateEvent :: JSM GType
gTypePopStateEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PopStateEvent"

-- | Functions for this inteface are in "JSDOM.PopStateEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PopStateEventInit Mozilla PopStateEventInit documentation>
newtype PopStateEventInit = PopStateEventInit { PopStateEventInit -> JSVal
unPopStateEventInit :: JSVal }

instance PToJSVal PopStateEventInit where
  pToJSVal :: PopStateEventInit -> JSVal
pToJSVal = PopStateEventInit -> JSVal
unPopStateEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal PopStateEventInit where
  pFromJSVal :: JSVal -> PopStateEventInit
pFromJSVal = JSVal -> PopStateEventInit
PopStateEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal PopStateEventInit where
  toJSVal :: PopStateEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PopStateEventInit -> JSVal) -> PopStateEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PopStateEventInit -> JSVal
unPopStateEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal PopStateEventInit where
  fromJSVal :: JSVal -> JSM (Maybe PopStateEventInit)
fromJSVal JSVal
v = (JSVal -> PopStateEventInit)
-> Maybe JSVal -> Maybe PopStateEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PopStateEventInit
PopStateEventInit (Maybe JSVal -> Maybe PopStateEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe PopStateEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PopStateEventInit
fromJSValUnchecked = PopStateEventInit -> JSM PopStateEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PopStateEventInit -> JSM PopStateEventInit)
-> (JSVal -> PopStateEventInit) -> JSVal -> JSM PopStateEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PopStateEventInit
PopStateEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PopStateEventInit where
  makeObject :: PopStateEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PopStateEventInit -> JSVal) -> PopStateEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PopStateEventInit -> JSVal
unPopStateEventInit

instance IsEventInit PopStateEventInit
instance IsGObject PopStateEventInit where
  typeGType :: PopStateEventInit -> JSM GType
typeGType PopStateEventInit
_ = JSM GType
gTypePopStateEventInit
  {-# INLINE typeGType #-}

noPopStateEventInit :: Maybe PopStateEventInit
noPopStateEventInit :: Maybe PopStateEventInit
noPopStateEventInit = Maybe PopStateEventInit
forall a. Maybe a
Nothing
{-# INLINE noPopStateEventInit #-}

gTypePopStateEventInit :: JSM GType
gTypePopStateEventInit :: JSM GType
gTypePopStateEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PopStateEventInit"

-- | Functions for this inteface are in "JSDOM.PositionError".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PositionError Mozilla PositionError documentation>
newtype PositionError = PositionError { PositionError -> JSVal
unPositionError :: JSVal }

instance PToJSVal PositionError where
  pToJSVal :: PositionError -> JSVal
pToJSVal = PositionError -> JSVal
unPositionError
  {-# INLINE pToJSVal #-}

instance PFromJSVal PositionError where
  pFromJSVal :: JSVal -> PositionError
pFromJSVal = JSVal -> PositionError
PositionError
  {-# INLINE pFromJSVal #-}

instance ToJSVal PositionError where
  toJSVal :: PositionError -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PositionError -> JSVal) -> PositionError -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionError -> JSVal
unPositionError
  {-# INLINE toJSVal #-}

instance FromJSVal PositionError where
  fromJSVal :: JSVal -> JSM (Maybe PositionError)
fromJSVal JSVal
v = (JSVal -> PositionError) -> Maybe JSVal -> Maybe PositionError
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PositionError
PositionError (Maybe JSVal -> Maybe PositionError)
-> JSM (Maybe JSVal) -> JSM (Maybe PositionError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PositionError
fromJSValUnchecked = PositionError -> JSM PositionError
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PositionError -> JSM PositionError)
-> (JSVal -> PositionError) -> JSVal -> JSM PositionError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PositionError
PositionError
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PositionError where
  makeObject :: PositionError -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PositionError -> JSVal) -> PositionError -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionError -> JSVal
unPositionError

instance IsGObject PositionError where
  typeGType :: PositionError -> JSM GType
typeGType PositionError
_ = JSM GType
gTypePositionError
  {-# INLINE typeGType #-}

noPositionError :: Maybe PositionError
noPositionError :: Maybe PositionError
noPositionError = Maybe PositionError
forall a. Maybe a
Nothing
{-# INLINE noPositionError #-}

gTypePositionError :: JSM GType
gTypePositionError :: JSM GType
gTypePositionError = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PositionError"

-- | Functions for this inteface are in "JSDOM.PositionOptions".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PositionOptions Mozilla PositionOptions documentation>
newtype PositionOptions = PositionOptions { PositionOptions -> JSVal
unPositionOptions :: JSVal }

instance PToJSVal PositionOptions where
  pToJSVal :: PositionOptions -> JSVal
pToJSVal = PositionOptions -> JSVal
unPositionOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal PositionOptions where
  pFromJSVal :: JSVal -> PositionOptions
pFromJSVal = JSVal -> PositionOptions
PositionOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal PositionOptions where
  toJSVal :: PositionOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PositionOptions -> JSVal) -> PositionOptions -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionOptions -> JSVal
unPositionOptions
  {-# INLINE toJSVal #-}

instance FromJSVal PositionOptions where
  fromJSVal :: JSVal -> JSM (Maybe PositionOptions)
fromJSVal JSVal
v = (JSVal -> PositionOptions) -> Maybe JSVal -> Maybe PositionOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PositionOptions
PositionOptions (Maybe JSVal -> Maybe PositionOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe PositionOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PositionOptions
fromJSValUnchecked = PositionOptions -> JSM PositionOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PositionOptions -> JSM PositionOptions)
-> (JSVal -> PositionOptions) -> JSVal -> JSM PositionOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PositionOptions
PositionOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PositionOptions where
  makeObject :: PositionOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PositionOptions -> JSVal) -> PositionOptions -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionOptions -> JSVal
unPositionOptions

instance IsGObject PositionOptions where
  typeGType :: PositionOptions -> JSM GType
typeGType PositionOptions
_ = JSM GType
gTypePositionOptions
  {-# INLINE typeGType #-}

noPositionOptions :: Maybe PositionOptions
noPositionOptions :: Maybe PositionOptions
noPositionOptions = Maybe PositionOptions
forall a. Maybe a
Nothing
{-# INLINE noPositionOptions #-}

gTypePositionOptions :: JSM GType
gTypePositionOptions :: JSM GType
gTypePositionOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PositionOptions"

-- | Functions for this inteface are in "JSDOM.ProcessingInstruction".
-- Base interface functions are in:
--
--     * "JSDOM.CharacterData"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.ChildNode"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ProcessingInstruction Mozilla ProcessingInstruction documentation>
newtype ProcessingInstruction = ProcessingInstruction { ProcessingInstruction -> JSVal
unProcessingInstruction :: JSVal }

instance PToJSVal ProcessingInstruction where
  pToJSVal :: ProcessingInstruction -> JSVal
pToJSVal = ProcessingInstruction -> JSVal
unProcessingInstruction
  {-# INLINE pToJSVal #-}

instance PFromJSVal ProcessingInstruction where
  pFromJSVal :: JSVal -> ProcessingInstruction
pFromJSVal = JSVal -> ProcessingInstruction
ProcessingInstruction
  {-# INLINE pFromJSVal #-}

instance ToJSVal ProcessingInstruction where
  toJSVal :: ProcessingInstruction -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ProcessingInstruction -> JSVal)
-> ProcessingInstruction
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessingInstruction -> JSVal
unProcessingInstruction
  {-# INLINE toJSVal #-}

instance FromJSVal ProcessingInstruction where
  fromJSVal :: JSVal -> JSM (Maybe ProcessingInstruction)
fromJSVal JSVal
v = (JSVal -> ProcessingInstruction)
-> Maybe JSVal -> Maybe ProcessingInstruction
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ProcessingInstruction
ProcessingInstruction (Maybe JSVal -> Maybe ProcessingInstruction)
-> JSM (Maybe JSVal) -> JSM (Maybe ProcessingInstruction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ProcessingInstruction
fromJSValUnchecked = ProcessingInstruction -> JSM ProcessingInstruction
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ProcessingInstruction -> JSM ProcessingInstruction)
-> (JSVal -> ProcessingInstruction)
-> JSVal
-> JSM ProcessingInstruction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ProcessingInstruction
ProcessingInstruction
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ProcessingInstruction where
  makeObject :: ProcessingInstruction -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ProcessingInstruction -> JSVal)
-> ProcessingInstruction
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessingInstruction -> JSVal
unProcessingInstruction

instance IsCharacterData ProcessingInstruction
instance IsNode ProcessingInstruction
instance IsEventTarget ProcessingInstruction
instance IsNonDocumentTypeChildNode ProcessingInstruction
instance IsChildNode ProcessingInstruction
instance IsGObject ProcessingInstruction where
  typeGType :: ProcessingInstruction -> JSM GType
typeGType ProcessingInstruction
_ = JSM GType
gTypeProcessingInstruction
  {-# INLINE typeGType #-}

noProcessingInstruction :: Maybe ProcessingInstruction
noProcessingInstruction :: Maybe ProcessingInstruction
noProcessingInstruction = Maybe ProcessingInstruction
forall a. Maybe a
Nothing
{-# INLINE noProcessingInstruction #-}

gTypeProcessingInstruction :: JSM GType
gTypeProcessingInstruction :: JSM GType
gTypeProcessingInstruction = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ProcessingInstruction"

-- | Functions for this inteface are in "JSDOM.ProgressEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ProgressEvent Mozilla ProgressEvent documentation>
newtype ProgressEvent = ProgressEvent { ProgressEvent -> JSVal
unProgressEvent :: JSVal }

instance PToJSVal ProgressEvent where
  pToJSVal :: ProgressEvent -> JSVal
pToJSVal = ProgressEvent -> JSVal
unProgressEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal ProgressEvent where
  pFromJSVal :: JSVal -> ProgressEvent
pFromJSVal = JSVal -> ProgressEvent
ProgressEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal ProgressEvent where
  toJSVal :: ProgressEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ProgressEvent -> JSVal) -> ProgressEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressEvent -> JSVal
unProgressEvent
  {-# INLINE toJSVal #-}

instance FromJSVal ProgressEvent where
  fromJSVal :: JSVal -> JSM (Maybe ProgressEvent)
fromJSVal JSVal
v = (JSVal -> ProgressEvent) -> Maybe JSVal -> Maybe ProgressEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ProgressEvent
ProgressEvent (Maybe JSVal -> Maybe ProgressEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe ProgressEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ProgressEvent
fromJSValUnchecked = ProgressEvent -> JSM ProgressEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ProgressEvent -> JSM ProgressEvent)
-> (JSVal -> ProgressEvent) -> JSVal -> JSM ProgressEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ProgressEvent
ProgressEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ProgressEvent where
  makeObject :: ProgressEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ProgressEvent -> JSVal) -> ProgressEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressEvent -> JSVal
unProgressEvent

class (IsEvent o, IsGObject o) => IsProgressEvent o
toProgressEvent :: IsProgressEvent o => o -> ProgressEvent
toProgressEvent :: forall o. IsProgressEvent o => o -> ProgressEvent
toProgressEvent = JSVal -> ProgressEvent
ProgressEvent (JSVal -> ProgressEvent) -> (o -> JSVal) -> o -> ProgressEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsProgressEvent ProgressEvent
instance IsEvent ProgressEvent
instance IsGObject ProgressEvent where
  typeGType :: ProgressEvent -> JSM GType
typeGType ProgressEvent
_ = JSM GType
gTypeProgressEvent
  {-# INLINE typeGType #-}

noProgressEvent :: Maybe ProgressEvent
noProgressEvent :: Maybe ProgressEvent
noProgressEvent = Maybe ProgressEvent
forall a. Maybe a
Nothing
{-# INLINE noProgressEvent #-}

gTypeProgressEvent :: JSM GType
gTypeProgressEvent :: JSM GType
gTypeProgressEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ProgressEvent"

-- | Functions for this inteface are in "JSDOM.ProgressEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ProgressEventInit Mozilla ProgressEventInit documentation>
newtype ProgressEventInit = ProgressEventInit { ProgressEventInit -> JSVal
unProgressEventInit :: JSVal }

instance PToJSVal ProgressEventInit where
  pToJSVal :: ProgressEventInit -> JSVal
pToJSVal = ProgressEventInit -> JSVal
unProgressEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal ProgressEventInit where
  pFromJSVal :: JSVal -> ProgressEventInit
pFromJSVal = JSVal -> ProgressEventInit
ProgressEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal ProgressEventInit where
  toJSVal :: ProgressEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ProgressEventInit -> JSVal) -> ProgressEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressEventInit -> JSVal
unProgressEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal ProgressEventInit where
  fromJSVal :: JSVal -> JSM (Maybe ProgressEventInit)
fromJSVal JSVal
v = (JSVal -> ProgressEventInit)
-> Maybe JSVal -> Maybe ProgressEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ProgressEventInit
ProgressEventInit (Maybe JSVal -> Maybe ProgressEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe ProgressEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ProgressEventInit
fromJSValUnchecked = ProgressEventInit -> JSM ProgressEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ProgressEventInit -> JSM ProgressEventInit)
-> (JSVal -> ProgressEventInit) -> JSVal -> JSM ProgressEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ProgressEventInit
ProgressEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ProgressEventInit where
  makeObject :: ProgressEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ProgressEventInit -> JSVal) -> ProgressEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgressEventInit -> JSVal
unProgressEventInit

instance IsEventInit ProgressEventInit
instance IsGObject ProgressEventInit where
  typeGType :: ProgressEventInit -> JSM GType
typeGType ProgressEventInit
_ = JSM GType
gTypeProgressEventInit
  {-# INLINE typeGType #-}

noProgressEventInit :: Maybe ProgressEventInit
noProgressEventInit :: Maybe ProgressEventInit
noProgressEventInit = Maybe ProgressEventInit
forall a. Maybe a
Nothing
{-# INLINE noProgressEventInit #-}

gTypeProgressEventInit :: JSM GType
gTypeProgressEventInit :: JSM GType
gTypeProgressEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ProgressEventInit"

-- | Functions for this inteface are in "JSDOM.PromiseRejectionEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PromiseRejectionEvent Mozilla PromiseRejectionEvent documentation>
newtype PromiseRejectionEvent = PromiseRejectionEvent { PromiseRejectionEvent -> JSVal
unPromiseRejectionEvent :: JSVal }

instance PToJSVal PromiseRejectionEvent where
  pToJSVal :: PromiseRejectionEvent -> JSVal
pToJSVal = PromiseRejectionEvent -> JSVal
unPromiseRejectionEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal PromiseRejectionEvent where
  pFromJSVal :: JSVal -> PromiseRejectionEvent
pFromJSVal = JSVal -> PromiseRejectionEvent
PromiseRejectionEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal PromiseRejectionEvent where
  toJSVal :: PromiseRejectionEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PromiseRejectionEvent -> JSVal)
-> PromiseRejectionEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PromiseRejectionEvent -> JSVal
unPromiseRejectionEvent
  {-# INLINE toJSVal #-}

instance FromJSVal PromiseRejectionEvent where
  fromJSVal :: JSVal -> JSM (Maybe PromiseRejectionEvent)
fromJSVal JSVal
v = (JSVal -> PromiseRejectionEvent)
-> Maybe JSVal -> Maybe PromiseRejectionEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PromiseRejectionEvent
PromiseRejectionEvent (Maybe JSVal -> Maybe PromiseRejectionEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe PromiseRejectionEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PromiseRejectionEvent
fromJSValUnchecked = PromiseRejectionEvent -> JSM PromiseRejectionEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PromiseRejectionEvent -> JSM PromiseRejectionEvent)
-> (JSVal -> PromiseRejectionEvent)
-> JSVal
-> JSM PromiseRejectionEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PromiseRejectionEvent
PromiseRejectionEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PromiseRejectionEvent where
  makeObject :: PromiseRejectionEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PromiseRejectionEvent -> JSVal)
-> PromiseRejectionEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PromiseRejectionEvent -> JSVal
unPromiseRejectionEvent

instance IsEvent PromiseRejectionEvent
instance IsGObject PromiseRejectionEvent where
  typeGType :: PromiseRejectionEvent -> JSM GType
typeGType PromiseRejectionEvent
_ = JSM GType
gTypePromiseRejectionEvent
  {-# INLINE typeGType #-}

noPromiseRejectionEvent :: Maybe PromiseRejectionEvent
noPromiseRejectionEvent :: Maybe PromiseRejectionEvent
noPromiseRejectionEvent = Maybe PromiseRejectionEvent
forall a. Maybe a
Nothing
{-# INLINE noPromiseRejectionEvent #-}

gTypePromiseRejectionEvent :: JSM GType
gTypePromiseRejectionEvent :: JSM GType
gTypePromiseRejectionEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PromiseRejectionEvent"

-- | Functions for this inteface are in "JSDOM.PromiseRejectionEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/PromiseRejectionEventInit Mozilla PromiseRejectionEventInit documentation>
newtype PromiseRejectionEventInit = PromiseRejectionEventInit { PromiseRejectionEventInit -> JSVal
unPromiseRejectionEventInit :: JSVal }

instance PToJSVal PromiseRejectionEventInit where
  pToJSVal :: PromiseRejectionEventInit -> JSVal
pToJSVal = PromiseRejectionEventInit -> JSVal
unPromiseRejectionEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal PromiseRejectionEventInit where
  pFromJSVal :: JSVal -> PromiseRejectionEventInit
pFromJSVal = JSVal -> PromiseRejectionEventInit
PromiseRejectionEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal PromiseRejectionEventInit where
  toJSVal :: PromiseRejectionEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (PromiseRejectionEventInit -> JSVal)
-> PromiseRejectionEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PromiseRejectionEventInit -> JSVal
unPromiseRejectionEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal PromiseRejectionEventInit where
  fromJSVal :: JSVal -> JSM (Maybe PromiseRejectionEventInit)
fromJSVal JSVal
v = (JSVal -> PromiseRejectionEventInit)
-> Maybe JSVal -> Maybe PromiseRejectionEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> PromiseRejectionEventInit
PromiseRejectionEventInit (Maybe JSVal -> Maybe PromiseRejectionEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe PromiseRejectionEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM PromiseRejectionEventInit
fromJSValUnchecked = PromiseRejectionEventInit -> JSM PromiseRejectionEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (PromiseRejectionEventInit -> JSM PromiseRejectionEventInit)
-> (JSVal -> PromiseRejectionEventInit)
-> JSVal
-> JSM PromiseRejectionEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> PromiseRejectionEventInit
PromiseRejectionEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject PromiseRejectionEventInit where
  makeObject :: PromiseRejectionEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (PromiseRejectionEventInit -> JSVal)
-> PromiseRejectionEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PromiseRejectionEventInit -> JSVal
unPromiseRejectionEventInit

instance IsEventInit PromiseRejectionEventInit
instance IsGObject PromiseRejectionEventInit where
  typeGType :: PromiseRejectionEventInit -> JSM GType
typeGType PromiseRejectionEventInit
_ = JSM GType
gTypePromiseRejectionEventInit
  {-# INLINE typeGType #-}

noPromiseRejectionEventInit :: Maybe PromiseRejectionEventInit
noPromiseRejectionEventInit :: Maybe PromiseRejectionEventInit
noPromiseRejectionEventInit = Maybe PromiseRejectionEventInit
forall a. Maybe a
Nothing
{-# INLINE noPromiseRejectionEventInit #-}

gTypePromiseRejectionEventInit :: JSM GType
gTypePromiseRejectionEventInit :: JSM GType
gTypePromiseRejectionEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"PromiseRejectionEventInit"

-- | Functions for this inteface are in "JSDOM.QuickTimePluginReplacement".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/QuickTimePluginReplacement Mozilla QuickTimePluginReplacement documentation>
newtype QuickTimePluginReplacement = QuickTimePluginReplacement { QuickTimePluginReplacement -> JSVal
unQuickTimePluginReplacement :: JSVal }

instance PToJSVal QuickTimePluginReplacement where
  pToJSVal :: QuickTimePluginReplacement -> JSVal
pToJSVal = QuickTimePluginReplacement -> JSVal
unQuickTimePluginReplacement
  {-# INLINE pToJSVal #-}

instance PFromJSVal QuickTimePluginReplacement where
  pFromJSVal :: JSVal -> QuickTimePluginReplacement
pFromJSVal = JSVal -> QuickTimePluginReplacement
QuickTimePluginReplacement
  {-# INLINE pFromJSVal #-}

instance ToJSVal QuickTimePluginReplacement where
  toJSVal :: QuickTimePluginReplacement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (QuickTimePluginReplacement -> JSVal)
-> QuickTimePluginReplacement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QuickTimePluginReplacement -> JSVal
unQuickTimePluginReplacement
  {-# INLINE toJSVal #-}

instance FromJSVal QuickTimePluginReplacement where
  fromJSVal :: JSVal -> JSM (Maybe QuickTimePluginReplacement)
fromJSVal JSVal
v = (JSVal -> QuickTimePluginReplacement)
-> Maybe JSVal -> Maybe QuickTimePluginReplacement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> QuickTimePluginReplacement
QuickTimePluginReplacement (Maybe JSVal -> Maybe QuickTimePluginReplacement)
-> JSM (Maybe JSVal) -> JSM (Maybe QuickTimePluginReplacement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM QuickTimePluginReplacement
fromJSValUnchecked = QuickTimePluginReplacement -> JSM QuickTimePluginReplacement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (QuickTimePluginReplacement -> JSM QuickTimePluginReplacement)
-> (JSVal -> QuickTimePluginReplacement)
-> JSVal
-> JSM QuickTimePluginReplacement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> QuickTimePluginReplacement
QuickTimePluginReplacement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject QuickTimePluginReplacement where
  makeObject :: QuickTimePluginReplacement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (QuickTimePluginReplacement -> JSVal)
-> QuickTimePluginReplacement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QuickTimePluginReplacement -> JSVal
unQuickTimePluginReplacement

instance IsGObject QuickTimePluginReplacement where
  typeGType :: QuickTimePluginReplacement -> JSM GType
typeGType QuickTimePluginReplacement
_ = JSM GType
gTypeQuickTimePluginReplacement
  {-# INLINE typeGType #-}

noQuickTimePluginReplacement :: Maybe QuickTimePluginReplacement
noQuickTimePluginReplacement :: Maybe QuickTimePluginReplacement
noQuickTimePluginReplacement = Maybe QuickTimePluginReplacement
forall a. Maybe a
Nothing
{-# INLINE noQuickTimePluginReplacement #-}

gTypeQuickTimePluginReplacement :: JSM GType
gTypeQuickTimePluginReplacement :: JSM GType
gTypeQuickTimePluginReplacement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"QuickTimePluginReplacement"

-- | Functions for this inteface are in "JSDOM.RGBColor".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RGBColor Mozilla RGBColor documentation>
newtype RGBColor = RGBColor { RGBColor -> JSVal
unRGBColor :: JSVal }

instance PToJSVal RGBColor where
  pToJSVal :: RGBColor -> JSVal
pToJSVal = RGBColor -> JSVal
unRGBColor
  {-# INLINE pToJSVal #-}

instance PFromJSVal RGBColor where
  pFromJSVal :: JSVal -> RGBColor
pFromJSVal = JSVal -> RGBColor
RGBColor
  {-# INLINE pFromJSVal #-}

instance ToJSVal RGBColor where
  toJSVal :: RGBColor -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RGBColor -> JSVal) -> RGBColor -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RGBColor -> JSVal
unRGBColor
  {-# INLINE toJSVal #-}

instance FromJSVal RGBColor where
  fromJSVal :: JSVal -> JSM (Maybe RGBColor)
fromJSVal JSVal
v = (JSVal -> RGBColor) -> Maybe JSVal -> Maybe RGBColor
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RGBColor
RGBColor (Maybe JSVal -> Maybe RGBColor)
-> JSM (Maybe JSVal) -> JSM (Maybe RGBColor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RGBColor
fromJSValUnchecked = RGBColor -> JSM RGBColor
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RGBColor -> JSM RGBColor)
-> (JSVal -> RGBColor) -> JSVal -> JSM RGBColor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RGBColor
RGBColor
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RGBColor where
  makeObject :: RGBColor -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RGBColor -> JSVal) -> RGBColor -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RGBColor -> JSVal
unRGBColor

instance IsGObject RGBColor where
  typeGType :: RGBColor -> JSM GType
typeGType RGBColor
_ = JSM GType
gTypeRGBColor
  {-# INLINE typeGType #-}

noRGBColor :: Maybe RGBColor
noRGBColor :: Maybe RGBColor
noRGBColor = Maybe RGBColor
forall a. Maybe a
Nothing
{-# INLINE noRGBColor #-}

gTypeRGBColor :: JSM GType
gTypeRGBColor :: JSM GType
gTypeRGBColor = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RGBColor"

-- | Functions for this inteface are in "JSDOM.RTCAnswerOptions".
-- Base interface functions are in:
--
--     * "JSDOM.RTCOfferAnswerOptions"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCAnswerOptions Mozilla RTCAnswerOptions documentation>
newtype RTCAnswerOptions = RTCAnswerOptions { RTCAnswerOptions -> JSVal
unRTCAnswerOptions :: JSVal }

instance PToJSVal RTCAnswerOptions where
  pToJSVal :: RTCAnswerOptions -> JSVal
pToJSVal = RTCAnswerOptions -> JSVal
unRTCAnswerOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCAnswerOptions where
  pFromJSVal :: JSVal -> RTCAnswerOptions
pFromJSVal = JSVal -> RTCAnswerOptions
RTCAnswerOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCAnswerOptions where
  toJSVal :: RTCAnswerOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCAnswerOptions -> JSVal) -> RTCAnswerOptions -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCAnswerOptions -> JSVal
unRTCAnswerOptions
  {-# INLINE toJSVal #-}

instance FromJSVal RTCAnswerOptions where
  fromJSVal :: JSVal -> JSM (Maybe RTCAnswerOptions)
fromJSVal JSVal
v = (JSVal -> RTCAnswerOptions)
-> Maybe JSVal -> Maybe RTCAnswerOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCAnswerOptions
RTCAnswerOptions (Maybe JSVal -> Maybe RTCAnswerOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCAnswerOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCAnswerOptions
fromJSValUnchecked = RTCAnswerOptions -> JSM RTCAnswerOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCAnswerOptions -> JSM RTCAnswerOptions)
-> (JSVal -> RTCAnswerOptions) -> JSVal -> JSM RTCAnswerOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCAnswerOptions
RTCAnswerOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCAnswerOptions where
  makeObject :: RTCAnswerOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCAnswerOptions -> JSVal) -> RTCAnswerOptions -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCAnswerOptions -> JSVal
unRTCAnswerOptions

instance IsRTCOfferAnswerOptions RTCAnswerOptions
instance IsGObject RTCAnswerOptions where
  typeGType :: RTCAnswerOptions -> JSM GType
typeGType RTCAnswerOptions
_ = JSM GType
gTypeRTCAnswerOptions
  {-# INLINE typeGType #-}

noRTCAnswerOptions :: Maybe RTCAnswerOptions
noRTCAnswerOptions :: Maybe RTCAnswerOptions
noRTCAnswerOptions = Maybe RTCAnswerOptions
forall a. Maybe a
Nothing
{-# INLINE noRTCAnswerOptions #-}

gTypeRTCAnswerOptions :: JSM GType
gTypeRTCAnswerOptions :: JSM GType
gTypeRTCAnswerOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCAnswerOptions"

-- | Functions for this inteface are in "JSDOM.RTCConfiguration".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCConfiguration Mozilla RTCConfiguration documentation>
newtype RTCConfiguration = RTCConfiguration { RTCConfiguration -> JSVal
unRTCConfiguration :: JSVal }

instance PToJSVal RTCConfiguration where
  pToJSVal :: RTCConfiguration -> JSVal
pToJSVal = RTCConfiguration -> JSVal
unRTCConfiguration
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCConfiguration where
  pFromJSVal :: JSVal -> RTCConfiguration
pFromJSVal = JSVal -> RTCConfiguration
RTCConfiguration
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCConfiguration where
  toJSVal :: RTCConfiguration -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCConfiguration -> JSVal) -> RTCConfiguration -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCConfiguration -> JSVal
unRTCConfiguration
  {-# INLINE toJSVal #-}

instance FromJSVal RTCConfiguration where
  fromJSVal :: JSVal -> JSM (Maybe RTCConfiguration)
fromJSVal JSVal
v = (JSVal -> RTCConfiguration)
-> Maybe JSVal -> Maybe RTCConfiguration
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCConfiguration
RTCConfiguration (Maybe JSVal -> Maybe RTCConfiguration)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCConfiguration)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCConfiguration
fromJSValUnchecked = RTCConfiguration -> JSM RTCConfiguration
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCConfiguration -> JSM RTCConfiguration)
-> (JSVal -> RTCConfiguration) -> JSVal -> JSM RTCConfiguration
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCConfiguration
RTCConfiguration
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCConfiguration where
  makeObject :: RTCConfiguration -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCConfiguration -> JSVal) -> RTCConfiguration -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCConfiguration -> JSVal
unRTCConfiguration

instance IsGObject RTCConfiguration where
  typeGType :: RTCConfiguration -> JSM GType
typeGType RTCConfiguration
_ = JSM GType
gTypeRTCConfiguration
  {-# INLINE typeGType #-}

noRTCConfiguration :: Maybe RTCConfiguration
noRTCConfiguration :: Maybe RTCConfiguration
noRTCConfiguration = Maybe RTCConfiguration
forall a. Maybe a
Nothing
{-# INLINE noRTCConfiguration #-}

gTypeRTCConfiguration :: JSM GType
gTypeRTCConfiguration :: JSM GType
gTypeRTCConfiguration = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCConfiguration"

-- | Functions for this inteface are in "JSDOM.RTCDTMFSender".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCDTMFSender Mozilla RTCDTMFSender documentation>
newtype RTCDTMFSender = RTCDTMFSender { RTCDTMFSender -> JSVal
unRTCDTMFSender :: JSVal }

instance PToJSVal RTCDTMFSender where
  pToJSVal :: RTCDTMFSender -> JSVal
pToJSVal = RTCDTMFSender -> JSVal
unRTCDTMFSender
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCDTMFSender where
  pFromJSVal :: JSVal -> RTCDTMFSender
pFromJSVal = JSVal -> RTCDTMFSender
RTCDTMFSender
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCDTMFSender where
  toJSVal :: RTCDTMFSender -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCDTMFSender -> JSVal) -> RTCDTMFSender -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDTMFSender -> JSVal
unRTCDTMFSender
  {-# INLINE toJSVal #-}

instance FromJSVal RTCDTMFSender where
  fromJSVal :: JSVal -> JSM (Maybe RTCDTMFSender)
fromJSVal JSVal
v = (JSVal -> RTCDTMFSender) -> Maybe JSVal -> Maybe RTCDTMFSender
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCDTMFSender
RTCDTMFSender (Maybe JSVal -> Maybe RTCDTMFSender)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCDTMFSender)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCDTMFSender
fromJSValUnchecked = RTCDTMFSender -> JSM RTCDTMFSender
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDTMFSender -> JSM RTCDTMFSender)
-> (JSVal -> RTCDTMFSender) -> JSVal -> JSM RTCDTMFSender
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCDTMFSender
RTCDTMFSender
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCDTMFSender where
  makeObject :: RTCDTMFSender -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCDTMFSender -> JSVal) -> RTCDTMFSender -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDTMFSender -> JSVal
unRTCDTMFSender

instance IsEventTarget RTCDTMFSender
instance IsGObject RTCDTMFSender where
  typeGType :: RTCDTMFSender -> JSM GType
typeGType RTCDTMFSender
_ = JSM GType
gTypeRTCDTMFSender
  {-# INLINE typeGType #-}

noRTCDTMFSender :: Maybe RTCDTMFSender
noRTCDTMFSender :: Maybe RTCDTMFSender
noRTCDTMFSender = Maybe RTCDTMFSender
forall a. Maybe a
Nothing
{-# INLINE noRTCDTMFSender #-}

gTypeRTCDTMFSender :: JSM GType
gTypeRTCDTMFSender :: JSM GType
gTypeRTCDTMFSender = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCDTMFSender"

-- | Functions for this inteface are in "JSDOM.RTCDTMFToneChangeEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCDTMFToneChangeEvent Mozilla RTCDTMFToneChangeEvent documentation>
newtype RTCDTMFToneChangeEvent = RTCDTMFToneChangeEvent { RTCDTMFToneChangeEvent -> JSVal
unRTCDTMFToneChangeEvent :: JSVal }

instance PToJSVal RTCDTMFToneChangeEvent where
  pToJSVal :: RTCDTMFToneChangeEvent -> JSVal
pToJSVal = RTCDTMFToneChangeEvent -> JSVal
unRTCDTMFToneChangeEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCDTMFToneChangeEvent where
  pFromJSVal :: JSVal -> RTCDTMFToneChangeEvent
pFromJSVal = JSVal -> RTCDTMFToneChangeEvent
RTCDTMFToneChangeEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCDTMFToneChangeEvent where
  toJSVal :: RTCDTMFToneChangeEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCDTMFToneChangeEvent -> JSVal)
-> RTCDTMFToneChangeEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDTMFToneChangeEvent -> JSVal
unRTCDTMFToneChangeEvent
  {-# INLINE toJSVal #-}

instance FromJSVal RTCDTMFToneChangeEvent where
  fromJSVal :: JSVal -> JSM (Maybe RTCDTMFToneChangeEvent)
fromJSVal JSVal
v = (JSVal -> RTCDTMFToneChangeEvent)
-> Maybe JSVal -> Maybe RTCDTMFToneChangeEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCDTMFToneChangeEvent
RTCDTMFToneChangeEvent (Maybe JSVal -> Maybe RTCDTMFToneChangeEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCDTMFToneChangeEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCDTMFToneChangeEvent
fromJSValUnchecked = RTCDTMFToneChangeEvent -> JSM RTCDTMFToneChangeEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDTMFToneChangeEvent -> JSM RTCDTMFToneChangeEvent)
-> (JSVal -> RTCDTMFToneChangeEvent)
-> JSVal
-> JSM RTCDTMFToneChangeEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCDTMFToneChangeEvent
RTCDTMFToneChangeEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCDTMFToneChangeEvent where
  makeObject :: RTCDTMFToneChangeEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCDTMFToneChangeEvent -> JSVal)
-> RTCDTMFToneChangeEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDTMFToneChangeEvent -> JSVal
unRTCDTMFToneChangeEvent

instance IsEvent RTCDTMFToneChangeEvent
instance IsGObject RTCDTMFToneChangeEvent where
  typeGType :: RTCDTMFToneChangeEvent -> JSM GType
typeGType RTCDTMFToneChangeEvent
_ = JSM GType
gTypeRTCDTMFToneChangeEvent
  {-# INLINE typeGType #-}

noRTCDTMFToneChangeEvent :: Maybe RTCDTMFToneChangeEvent
noRTCDTMFToneChangeEvent :: Maybe RTCDTMFToneChangeEvent
noRTCDTMFToneChangeEvent = Maybe RTCDTMFToneChangeEvent
forall a. Maybe a
Nothing
{-# INLINE noRTCDTMFToneChangeEvent #-}

gTypeRTCDTMFToneChangeEvent :: JSM GType
gTypeRTCDTMFToneChangeEvent :: JSM GType
gTypeRTCDTMFToneChangeEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCDTMFToneChangeEvent"

-- | Functions for this inteface are in "JSDOM.RTCDTMFToneChangeEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCDTMFToneChangeEventInit Mozilla RTCDTMFToneChangeEventInit documentation>
newtype RTCDTMFToneChangeEventInit = RTCDTMFToneChangeEventInit { RTCDTMFToneChangeEventInit -> JSVal
unRTCDTMFToneChangeEventInit :: JSVal }

instance PToJSVal RTCDTMFToneChangeEventInit where
  pToJSVal :: RTCDTMFToneChangeEventInit -> JSVal
pToJSVal = RTCDTMFToneChangeEventInit -> JSVal
unRTCDTMFToneChangeEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCDTMFToneChangeEventInit where
  pFromJSVal :: JSVal -> RTCDTMFToneChangeEventInit
pFromJSVal = JSVal -> RTCDTMFToneChangeEventInit
RTCDTMFToneChangeEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCDTMFToneChangeEventInit where
  toJSVal :: RTCDTMFToneChangeEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCDTMFToneChangeEventInit -> JSVal)
-> RTCDTMFToneChangeEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDTMFToneChangeEventInit -> JSVal
unRTCDTMFToneChangeEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal RTCDTMFToneChangeEventInit where
  fromJSVal :: JSVal -> JSM (Maybe RTCDTMFToneChangeEventInit)
fromJSVal JSVal
v = (JSVal -> RTCDTMFToneChangeEventInit)
-> Maybe JSVal -> Maybe RTCDTMFToneChangeEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCDTMFToneChangeEventInit
RTCDTMFToneChangeEventInit (Maybe JSVal -> Maybe RTCDTMFToneChangeEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCDTMFToneChangeEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCDTMFToneChangeEventInit
fromJSValUnchecked = RTCDTMFToneChangeEventInit -> JSM RTCDTMFToneChangeEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDTMFToneChangeEventInit -> JSM RTCDTMFToneChangeEventInit)
-> (JSVal -> RTCDTMFToneChangeEventInit)
-> JSVal
-> JSM RTCDTMFToneChangeEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCDTMFToneChangeEventInit
RTCDTMFToneChangeEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCDTMFToneChangeEventInit where
  makeObject :: RTCDTMFToneChangeEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCDTMFToneChangeEventInit -> JSVal)
-> RTCDTMFToneChangeEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDTMFToneChangeEventInit -> JSVal
unRTCDTMFToneChangeEventInit

instance IsEventInit RTCDTMFToneChangeEventInit
instance IsGObject RTCDTMFToneChangeEventInit where
  typeGType :: RTCDTMFToneChangeEventInit -> JSM GType
typeGType RTCDTMFToneChangeEventInit
_ = JSM GType
gTypeRTCDTMFToneChangeEventInit
  {-# INLINE typeGType #-}

noRTCDTMFToneChangeEventInit :: Maybe RTCDTMFToneChangeEventInit
noRTCDTMFToneChangeEventInit :: Maybe RTCDTMFToneChangeEventInit
noRTCDTMFToneChangeEventInit = Maybe RTCDTMFToneChangeEventInit
forall a. Maybe a
Nothing
{-# INLINE noRTCDTMFToneChangeEventInit #-}

gTypeRTCDTMFToneChangeEventInit :: JSM GType
gTypeRTCDTMFToneChangeEventInit :: JSM GType
gTypeRTCDTMFToneChangeEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCDTMFToneChangeEventInit"

-- | Functions for this inteface are in "JSDOM.RTCDataChannel".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCDataChannel Mozilla RTCDataChannel documentation>
newtype RTCDataChannel = RTCDataChannel { RTCDataChannel -> JSVal
unRTCDataChannel :: JSVal }

instance PToJSVal RTCDataChannel where
  pToJSVal :: RTCDataChannel -> JSVal
pToJSVal = RTCDataChannel -> JSVal
unRTCDataChannel
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCDataChannel where
  pFromJSVal :: JSVal -> RTCDataChannel
pFromJSVal = JSVal -> RTCDataChannel
RTCDataChannel
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCDataChannel where
  toJSVal :: RTCDataChannel -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCDataChannel -> JSVal) -> RTCDataChannel -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDataChannel -> JSVal
unRTCDataChannel
  {-# INLINE toJSVal #-}

instance FromJSVal RTCDataChannel where
  fromJSVal :: JSVal -> JSM (Maybe RTCDataChannel)
fromJSVal JSVal
v = (JSVal -> RTCDataChannel) -> Maybe JSVal -> Maybe RTCDataChannel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCDataChannel
RTCDataChannel (Maybe JSVal -> Maybe RTCDataChannel)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCDataChannel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCDataChannel
fromJSValUnchecked = RTCDataChannel -> JSM RTCDataChannel
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDataChannel -> JSM RTCDataChannel)
-> (JSVal -> RTCDataChannel) -> JSVal -> JSM RTCDataChannel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCDataChannel
RTCDataChannel
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCDataChannel where
  makeObject :: RTCDataChannel -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCDataChannel -> JSVal) -> RTCDataChannel -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDataChannel -> JSVal
unRTCDataChannel

instance IsEventTarget RTCDataChannel
instance IsGObject RTCDataChannel where
  typeGType :: RTCDataChannel -> JSM GType
typeGType RTCDataChannel
_ = JSM GType
gTypeRTCDataChannel
  {-# INLINE typeGType #-}

noRTCDataChannel :: Maybe RTCDataChannel
noRTCDataChannel :: Maybe RTCDataChannel
noRTCDataChannel = Maybe RTCDataChannel
forall a. Maybe a
Nothing
{-# INLINE noRTCDataChannel #-}

gTypeRTCDataChannel :: JSM GType
gTypeRTCDataChannel :: JSM GType
gTypeRTCDataChannel = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCDataChannel"

-- | Functions for this inteface are in "JSDOM.RTCDataChannelEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCDataChannelEvent Mozilla RTCDataChannelEvent documentation>
newtype RTCDataChannelEvent = RTCDataChannelEvent { RTCDataChannelEvent -> JSVal
unRTCDataChannelEvent :: JSVal }

instance PToJSVal RTCDataChannelEvent where
  pToJSVal :: RTCDataChannelEvent -> JSVal
pToJSVal = RTCDataChannelEvent -> JSVal
unRTCDataChannelEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCDataChannelEvent where
  pFromJSVal :: JSVal -> RTCDataChannelEvent
pFromJSVal = JSVal -> RTCDataChannelEvent
RTCDataChannelEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCDataChannelEvent where
  toJSVal :: RTCDataChannelEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCDataChannelEvent -> JSVal)
-> RTCDataChannelEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDataChannelEvent -> JSVal
unRTCDataChannelEvent
  {-# INLINE toJSVal #-}

instance FromJSVal RTCDataChannelEvent where
  fromJSVal :: JSVal -> JSM (Maybe RTCDataChannelEvent)
fromJSVal JSVal
v = (JSVal -> RTCDataChannelEvent)
-> Maybe JSVal -> Maybe RTCDataChannelEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCDataChannelEvent
RTCDataChannelEvent (Maybe JSVal -> Maybe RTCDataChannelEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCDataChannelEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCDataChannelEvent
fromJSValUnchecked = RTCDataChannelEvent -> JSM RTCDataChannelEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDataChannelEvent -> JSM RTCDataChannelEvent)
-> (JSVal -> RTCDataChannelEvent)
-> JSVal
-> JSM RTCDataChannelEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCDataChannelEvent
RTCDataChannelEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCDataChannelEvent where
  makeObject :: RTCDataChannelEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCDataChannelEvent -> JSVal)
-> RTCDataChannelEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDataChannelEvent -> JSVal
unRTCDataChannelEvent

instance IsEvent RTCDataChannelEvent
instance IsGObject RTCDataChannelEvent where
  typeGType :: RTCDataChannelEvent -> JSM GType
typeGType RTCDataChannelEvent
_ = JSM GType
gTypeRTCDataChannelEvent
  {-# INLINE typeGType #-}

noRTCDataChannelEvent :: Maybe RTCDataChannelEvent
noRTCDataChannelEvent :: Maybe RTCDataChannelEvent
noRTCDataChannelEvent = Maybe RTCDataChannelEvent
forall a. Maybe a
Nothing
{-# INLINE noRTCDataChannelEvent #-}

gTypeRTCDataChannelEvent :: JSM GType
gTypeRTCDataChannelEvent :: JSM GType
gTypeRTCDataChannelEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCDataChannelEvent"

-- | Functions for this inteface are in "JSDOM.RTCDataChannelEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCDataChannelEventInit Mozilla RTCDataChannelEventInit documentation>
newtype RTCDataChannelEventInit = RTCDataChannelEventInit { RTCDataChannelEventInit -> JSVal
unRTCDataChannelEventInit :: JSVal }

instance PToJSVal RTCDataChannelEventInit where
  pToJSVal :: RTCDataChannelEventInit -> JSVal
pToJSVal = RTCDataChannelEventInit -> JSVal
unRTCDataChannelEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCDataChannelEventInit where
  pFromJSVal :: JSVal -> RTCDataChannelEventInit
pFromJSVal = JSVal -> RTCDataChannelEventInit
RTCDataChannelEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCDataChannelEventInit where
  toJSVal :: RTCDataChannelEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCDataChannelEventInit -> JSVal)
-> RTCDataChannelEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDataChannelEventInit -> JSVal
unRTCDataChannelEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal RTCDataChannelEventInit where
  fromJSVal :: JSVal -> JSM (Maybe RTCDataChannelEventInit)
fromJSVal JSVal
v = (JSVal -> RTCDataChannelEventInit)
-> Maybe JSVal -> Maybe RTCDataChannelEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCDataChannelEventInit
RTCDataChannelEventInit (Maybe JSVal -> Maybe RTCDataChannelEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCDataChannelEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCDataChannelEventInit
fromJSValUnchecked = RTCDataChannelEventInit -> JSM RTCDataChannelEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDataChannelEventInit -> JSM RTCDataChannelEventInit)
-> (JSVal -> RTCDataChannelEventInit)
-> JSVal
-> JSM RTCDataChannelEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCDataChannelEventInit
RTCDataChannelEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCDataChannelEventInit where
  makeObject :: RTCDataChannelEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCDataChannelEventInit -> JSVal)
-> RTCDataChannelEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDataChannelEventInit -> JSVal
unRTCDataChannelEventInit

instance IsEventInit RTCDataChannelEventInit
instance IsGObject RTCDataChannelEventInit where
  typeGType :: RTCDataChannelEventInit -> JSM GType
typeGType RTCDataChannelEventInit
_ = JSM GType
gTypeRTCDataChannelEventInit
  {-# INLINE typeGType #-}

noRTCDataChannelEventInit :: Maybe RTCDataChannelEventInit
noRTCDataChannelEventInit :: Maybe RTCDataChannelEventInit
noRTCDataChannelEventInit = Maybe RTCDataChannelEventInit
forall a. Maybe a
Nothing
{-# INLINE noRTCDataChannelEventInit #-}

gTypeRTCDataChannelEventInit :: JSM GType
gTypeRTCDataChannelEventInit :: JSM GType
gTypeRTCDataChannelEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCDataChannelEventInit"

-- | Functions for this inteface are in "JSDOM.RTCDataChannelInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCDataChannelInit Mozilla RTCDataChannelInit documentation>
newtype RTCDataChannelInit = RTCDataChannelInit { RTCDataChannelInit -> JSVal
unRTCDataChannelInit :: JSVal }

instance PToJSVal RTCDataChannelInit where
  pToJSVal :: RTCDataChannelInit -> JSVal
pToJSVal = RTCDataChannelInit -> JSVal
unRTCDataChannelInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCDataChannelInit where
  pFromJSVal :: JSVal -> RTCDataChannelInit
pFromJSVal = JSVal -> RTCDataChannelInit
RTCDataChannelInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCDataChannelInit where
  toJSVal :: RTCDataChannelInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCDataChannelInit -> JSVal) -> RTCDataChannelInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDataChannelInit -> JSVal
unRTCDataChannelInit
  {-# INLINE toJSVal #-}

instance FromJSVal RTCDataChannelInit where
  fromJSVal :: JSVal -> JSM (Maybe RTCDataChannelInit)
fromJSVal JSVal
v = (JSVal -> RTCDataChannelInit)
-> Maybe JSVal -> Maybe RTCDataChannelInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCDataChannelInit
RTCDataChannelInit (Maybe JSVal -> Maybe RTCDataChannelInit)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCDataChannelInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCDataChannelInit
fromJSValUnchecked = RTCDataChannelInit -> JSM RTCDataChannelInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDataChannelInit -> JSM RTCDataChannelInit)
-> (JSVal -> RTCDataChannelInit) -> JSVal -> JSM RTCDataChannelInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCDataChannelInit
RTCDataChannelInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCDataChannelInit where
  makeObject :: RTCDataChannelInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCDataChannelInit -> JSVal)
-> RTCDataChannelInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDataChannelInit -> JSVal
unRTCDataChannelInit

instance IsGObject RTCDataChannelInit where
  typeGType :: RTCDataChannelInit -> JSM GType
typeGType RTCDataChannelInit
_ = JSM GType
gTypeRTCDataChannelInit
  {-# INLINE typeGType #-}

noRTCDataChannelInit :: Maybe RTCDataChannelInit
noRTCDataChannelInit :: Maybe RTCDataChannelInit
noRTCDataChannelInit = Maybe RTCDataChannelInit
forall a. Maybe a
Nothing
{-# INLINE noRTCDataChannelInit #-}

gTypeRTCDataChannelInit :: JSM GType
gTypeRTCDataChannelInit :: JSM GType
gTypeRTCDataChannelInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCDataChannelInit"

-- | Functions for this inteface are in "JSDOM.RTCDataChannelStats".
-- Base interface functions are in:
--
--     * "JSDOM.RTCStats"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCDataChannelStats Mozilla RTCDataChannelStats documentation>
newtype RTCDataChannelStats = RTCDataChannelStats { RTCDataChannelStats -> JSVal
unRTCDataChannelStats :: JSVal }

instance PToJSVal RTCDataChannelStats where
  pToJSVal :: RTCDataChannelStats -> JSVal
pToJSVal = RTCDataChannelStats -> JSVal
unRTCDataChannelStats
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCDataChannelStats where
  pFromJSVal :: JSVal -> RTCDataChannelStats
pFromJSVal = JSVal -> RTCDataChannelStats
RTCDataChannelStats
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCDataChannelStats where
  toJSVal :: RTCDataChannelStats -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCDataChannelStats -> JSVal)
-> RTCDataChannelStats
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDataChannelStats -> JSVal
unRTCDataChannelStats
  {-# INLINE toJSVal #-}

instance FromJSVal RTCDataChannelStats where
  fromJSVal :: JSVal -> JSM (Maybe RTCDataChannelStats)
fromJSVal JSVal
v = (JSVal -> RTCDataChannelStats)
-> Maybe JSVal -> Maybe RTCDataChannelStats
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCDataChannelStats
RTCDataChannelStats (Maybe JSVal -> Maybe RTCDataChannelStats)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCDataChannelStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCDataChannelStats
fromJSValUnchecked = RTCDataChannelStats -> JSM RTCDataChannelStats
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDataChannelStats -> JSM RTCDataChannelStats)
-> (JSVal -> RTCDataChannelStats)
-> JSVal
-> JSM RTCDataChannelStats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCDataChannelStats
RTCDataChannelStats
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCDataChannelStats where
  makeObject :: RTCDataChannelStats -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCDataChannelStats -> JSVal)
-> RTCDataChannelStats
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCDataChannelStats -> JSVal
unRTCDataChannelStats

instance IsRTCStats RTCDataChannelStats
instance IsGObject RTCDataChannelStats where
  typeGType :: RTCDataChannelStats -> JSM GType
typeGType RTCDataChannelStats
_ = JSM GType
gTypeRTCDataChannelStats
  {-# INLINE typeGType #-}

noRTCDataChannelStats :: Maybe RTCDataChannelStats
noRTCDataChannelStats :: Maybe RTCDataChannelStats
noRTCDataChannelStats = Maybe RTCDataChannelStats
forall a. Maybe a
Nothing
{-# INLINE noRTCDataChannelStats #-}

gTypeRTCDataChannelStats :: JSM GType
gTypeRTCDataChannelStats :: JSM GType
gTypeRTCDataChannelStats = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCDataChannelStats"

-- | Functions for this inteface are in "JSDOM.RTCIceCandidate".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCIceCandidate Mozilla RTCIceCandidate documentation>
newtype RTCIceCandidate = RTCIceCandidate { RTCIceCandidate -> JSVal
unRTCIceCandidate :: JSVal }

instance PToJSVal RTCIceCandidate where
  pToJSVal :: RTCIceCandidate -> JSVal
pToJSVal = RTCIceCandidate -> JSVal
unRTCIceCandidate
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCIceCandidate where
  pFromJSVal :: JSVal -> RTCIceCandidate
pFromJSVal = JSVal -> RTCIceCandidate
RTCIceCandidate
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCIceCandidate where
  toJSVal :: RTCIceCandidate -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCIceCandidate -> JSVal) -> RTCIceCandidate -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceCandidate -> JSVal
unRTCIceCandidate
  {-# INLINE toJSVal #-}

instance FromJSVal RTCIceCandidate where
  fromJSVal :: JSVal -> JSM (Maybe RTCIceCandidate)
fromJSVal JSVal
v = (JSVal -> RTCIceCandidate) -> Maybe JSVal -> Maybe RTCIceCandidate
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCIceCandidate
RTCIceCandidate (Maybe JSVal -> Maybe RTCIceCandidate)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCIceCandidate)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCIceCandidate
fromJSValUnchecked = RTCIceCandidate -> JSM RTCIceCandidate
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceCandidate -> JSM RTCIceCandidate)
-> (JSVal -> RTCIceCandidate) -> JSVal -> JSM RTCIceCandidate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCIceCandidate
RTCIceCandidate
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCIceCandidate where
  makeObject :: RTCIceCandidate -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCIceCandidate -> JSVal) -> RTCIceCandidate -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceCandidate -> JSVal
unRTCIceCandidate

instance IsGObject RTCIceCandidate where
  typeGType :: RTCIceCandidate -> JSM GType
typeGType RTCIceCandidate
_ = JSM GType
gTypeRTCIceCandidate
  {-# INLINE typeGType #-}

noRTCIceCandidate :: Maybe RTCIceCandidate
noRTCIceCandidate :: Maybe RTCIceCandidate
noRTCIceCandidate = Maybe RTCIceCandidate
forall a. Maybe a
Nothing
{-# INLINE noRTCIceCandidate #-}

gTypeRTCIceCandidate :: JSM GType
gTypeRTCIceCandidate :: JSM GType
gTypeRTCIceCandidate = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCIceCandidate"

-- | Functions for this inteface are in "JSDOM.RTCIceCandidateEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCIceCandidateEvent Mozilla RTCIceCandidateEvent documentation>
newtype RTCIceCandidateEvent = RTCIceCandidateEvent { RTCIceCandidateEvent -> JSVal
unRTCIceCandidateEvent :: JSVal }

instance PToJSVal RTCIceCandidateEvent where
  pToJSVal :: RTCIceCandidateEvent -> JSVal
pToJSVal = RTCIceCandidateEvent -> JSVal
unRTCIceCandidateEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCIceCandidateEvent where
  pFromJSVal :: JSVal -> RTCIceCandidateEvent
pFromJSVal = JSVal -> RTCIceCandidateEvent
RTCIceCandidateEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCIceCandidateEvent where
  toJSVal :: RTCIceCandidateEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCIceCandidateEvent -> JSVal)
-> RTCIceCandidateEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceCandidateEvent -> JSVal
unRTCIceCandidateEvent
  {-# INLINE toJSVal #-}

instance FromJSVal RTCIceCandidateEvent where
  fromJSVal :: JSVal -> JSM (Maybe RTCIceCandidateEvent)
fromJSVal JSVal
v = (JSVal -> RTCIceCandidateEvent)
-> Maybe JSVal -> Maybe RTCIceCandidateEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCIceCandidateEvent
RTCIceCandidateEvent (Maybe JSVal -> Maybe RTCIceCandidateEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCIceCandidateEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCIceCandidateEvent
fromJSValUnchecked = RTCIceCandidateEvent -> JSM RTCIceCandidateEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceCandidateEvent -> JSM RTCIceCandidateEvent)
-> (JSVal -> RTCIceCandidateEvent)
-> JSVal
-> JSM RTCIceCandidateEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCIceCandidateEvent
RTCIceCandidateEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCIceCandidateEvent where
  makeObject :: RTCIceCandidateEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCIceCandidateEvent -> JSVal)
-> RTCIceCandidateEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceCandidateEvent -> JSVal
unRTCIceCandidateEvent

instance IsEvent RTCIceCandidateEvent
instance IsGObject RTCIceCandidateEvent where
  typeGType :: RTCIceCandidateEvent -> JSM GType
typeGType RTCIceCandidateEvent
_ = JSM GType
gTypeRTCIceCandidateEvent
  {-# INLINE typeGType #-}

noRTCIceCandidateEvent :: Maybe RTCIceCandidateEvent
noRTCIceCandidateEvent :: Maybe RTCIceCandidateEvent
noRTCIceCandidateEvent = Maybe RTCIceCandidateEvent
forall a. Maybe a
Nothing
{-# INLINE noRTCIceCandidateEvent #-}

gTypeRTCIceCandidateEvent :: JSM GType
gTypeRTCIceCandidateEvent :: JSM GType
gTypeRTCIceCandidateEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCIceCandidateEvent"

-- | Functions for this inteface are in "JSDOM.RTCIceCandidateInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCIceCandidateInit Mozilla RTCIceCandidateInit documentation>
newtype RTCIceCandidateInit = RTCIceCandidateInit { RTCIceCandidateInit -> JSVal
unRTCIceCandidateInit :: JSVal }

instance PToJSVal RTCIceCandidateInit where
  pToJSVal :: RTCIceCandidateInit -> JSVal
pToJSVal = RTCIceCandidateInit -> JSVal
unRTCIceCandidateInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCIceCandidateInit where
  pFromJSVal :: JSVal -> RTCIceCandidateInit
pFromJSVal = JSVal -> RTCIceCandidateInit
RTCIceCandidateInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCIceCandidateInit where
  toJSVal :: RTCIceCandidateInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCIceCandidateInit -> JSVal)
-> RTCIceCandidateInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceCandidateInit -> JSVal
unRTCIceCandidateInit
  {-# INLINE toJSVal #-}

instance FromJSVal RTCIceCandidateInit where
  fromJSVal :: JSVal -> JSM (Maybe RTCIceCandidateInit)
fromJSVal JSVal
v = (JSVal -> RTCIceCandidateInit)
-> Maybe JSVal -> Maybe RTCIceCandidateInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCIceCandidateInit
RTCIceCandidateInit (Maybe JSVal -> Maybe RTCIceCandidateInit)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCIceCandidateInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCIceCandidateInit
fromJSValUnchecked = RTCIceCandidateInit -> JSM RTCIceCandidateInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceCandidateInit -> JSM RTCIceCandidateInit)
-> (JSVal -> RTCIceCandidateInit)
-> JSVal
-> JSM RTCIceCandidateInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCIceCandidateInit
RTCIceCandidateInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCIceCandidateInit where
  makeObject :: RTCIceCandidateInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCIceCandidateInit -> JSVal)
-> RTCIceCandidateInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceCandidateInit -> JSVal
unRTCIceCandidateInit

instance IsGObject RTCIceCandidateInit where
  typeGType :: RTCIceCandidateInit -> JSM GType
typeGType RTCIceCandidateInit
_ = JSM GType
gTypeRTCIceCandidateInit
  {-# INLINE typeGType #-}

noRTCIceCandidateInit :: Maybe RTCIceCandidateInit
noRTCIceCandidateInit :: Maybe RTCIceCandidateInit
noRTCIceCandidateInit = Maybe RTCIceCandidateInit
forall a. Maybe a
Nothing
{-# INLINE noRTCIceCandidateInit #-}

gTypeRTCIceCandidateInit :: JSM GType
gTypeRTCIceCandidateInit :: JSM GType
gTypeRTCIceCandidateInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCIceCandidateInit"

-- | Functions for this inteface are in "JSDOM.RTCIceServer".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCIceServer Mozilla RTCIceServer documentation>
newtype RTCIceServer = RTCIceServer { RTCIceServer -> JSVal
unRTCIceServer :: JSVal }

instance PToJSVal RTCIceServer where
  pToJSVal :: RTCIceServer -> JSVal
pToJSVal = RTCIceServer -> JSVal
unRTCIceServer
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCIceServer where
  pFromJSVal :: JSVal -> RTCIceServer
pFromJSVal = JSVal -> RTCIceServer
RTCIceServer
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCIceServer where
  toJSVal :: RTCIceServer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCIceServer -> JSVal) -> RTCIceServer -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceServer -> JSVal
unRTCIceServer
  {-# INLINE toJSVal #-}

instance FromJSVal RTCIceServer where
  fromJSVal :: JSVal -> JSM (Maybe RTCIceServer)
fromJSVal JSVal
v = (JSVal -> RTCIceServer) -> Maybe JSVal -> Maybe RTCIceServer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCIceServer
RTCIceServer (Maybe JSVal -> Maybe RTCIceServer)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCIceServer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCIceServer
fromJSValUnchecked = RTCIceServer -> JSM RTCIceServer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceServer -> JSM RTCIceServer)
-> (JSVal -> RTCIceServer) -> JSVal -> JSM RTCIceServer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCIceServer
RTCIceServer
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCIceServer where
  makeObject :: RTCIceServer -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCIceServer -> JSVal) -> RTCIceServer -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceServer -> JSVal
unRTCIceServer

instance IsGObject RTCIceServer where
  typeGType :: RTCIceServer -> JSM GType
typeGType RTCIceServer
_ = JSM GType
gTypeRTCIceServer
  {-# INLINE typeGType #-}

noRTCIceServer :: Maybe RTCIceServer
noRTCIceServer :: Maybe RTCIceServer
noRTCIceServer = Maybe RTCIceServer
forall a. Maybe a
Nothing
{-# INLINE noRTCIceServer #-}

gTypeRTCIceServer :: JSM GType
gTypeRTCIceServer :: JSM GType
gTypeRTCIceServer = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCIceServer"

-- | Functions for this inteface are in "JSDOM.RTCIceTransport".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCIceTransport Mozilla RTCIceTransport documentation>
newtype RTCIceTransport = RTCIceTransport { RTCIceTransport -> JSVal
unRTCIceTransport :: JSVal }

instance PToJSVal RTCIceTransport where
  pToJSVal :: RTCIceTransport -> JSVal
pToJSVal = RTCIceTransport -> JSVal
unRTCIceTransport
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCIceTransport where
  pFromJSVal :: JSVal -> RTCIceTransport
pFromJSVal = JSVal -> RTCIceTransport
RTCIceTransport
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCIceTransport where
  toJSVal :: RTCIceTransport -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCIceTransport -> JSVal) -> RTCIceTransport -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceTransport -> JSVal
unRTCIceTransport
  {-# INLINE toJSVal #-}

instance FromJSVal RTCIceTransport where
  fromJSVal :: JSVal -> JSM (Maybe RTCIceTransport)
fromJSVal JSVal
v = (JSVal -> RTCIceTransport) -> Maybe JSVal -> Maybe RTCIceTransport
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCIceTransport
RTCIceTransport (Maybe JSVal -> Maybe RTCIceTransport)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCIceTransport)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCIceTransport
fromJSValUnchecked = RTCIceTransport -> JSM RTCIceTransport
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceTransport -> JSM RTCIceTransport)
-> (JSVal -> RTCIceTransport) -> JSVal -> JSM RTCIceTransport
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCIceTransport
RTCIceTransport
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCIceTransport where
  makeObject :: RTCIceTransport -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCIceTransport -> JSVal) -> RTCIceTransport -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCIceTransport -> JSVal
unRTCIceTransport

instance IsGObject RTCIceTransport where
  typeGType :: RTCIceTransport -> JSM GType
typeGType RTCIceTransport
_ = JSM GType
gTypeRTCIceTransport
  {-# INLINE typeGType #-}

noRTCIceTransport :: Maybe RTCIceTransport
noRTCIceTransport :: Maybe RTCIceTransport
noRTCIceTransport = Maybe RTCIceTransport
forall a. Maybe a
Nothing
{-# INLINE noRTCIceTransport #-}

gTypeRTCIceTransport :: JSM GType
gTypeRTCIceTransport :: JSM GType
gTypeRTCIceTransport = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCIceTransport"

-- | Functions for this inteface are in "JSDOM.RTCInboundRTPStreamStats".
-- Base interface functions are in:
--
--     * "JSDOM.RTCRTPStreamStats"
--     * "JSDOM.RTCStats"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCInboundRTPStreamStats Mozilla RTCInboundRTPStreamStats documentation>
newtype RTCInboundRTPStreamStats = RTCInboundRTPStreamStats { RTCInboundRTPStreamStats -> JSVal
unRTCInboundRTPStreamStats :: JSVal }

instance PToJSVal RTCInboundRTPStreamStats where
  pToJSVal :: RTCInboundRTPStreamStats -> JSVal
pToJSVal = RTCInboundRTPStreamStats -> JSVal
unRTCInboundRTPStreamStats
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCInboundRTPStreamStats where
  pFromJSVal :: JSVal -> RTCInboundRTPStreamStats
pFromJSVal = JSVal -> RTCInboundRTPStreamStats
RTCInboundRTPStreamStats
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCInboundRTPStreamStats where
  toJSVal :: RTCInboundRTPStreamStats -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCInboundRTPStreamStats -> JSVal)
-> RTCInboundRTPStreamStats
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCInboundRTPStreamStats -> JSVal
unRTCInboundRTPStreamStats
  {-# INLINE toJSVal #-}

instance FromJSVal RTCInboundRTPStreamStats where
  fromJSVal :: JSVal -> JSM (Maybe RTCInboundRTPStreamStats)
fromJSVal JSVal
v = (JSVal -> RTCInboundRTPStreamStats)
-> Maybe JSVal -> Maybe RTCInboundRTPStreamStats
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCInboundRTPStreamStats
RTCInboundRTPStreamStats (Maybe JSVal -> Maybe RTCInboundRTPStreamStats)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCInboundRTPStreamStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCInboundRTPStreamStats
fromJSValUnchecked = RTCInboundRTPStreamStats -> JSM RTCInboundRTPStreamStats
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCInboundRTPStreamStats -> JSM RTCInboundRTPStreamStats)
-> (JSVal -> RTCInboundRTPStreamStats)
-> JSVal
-> JSM RTCInboundRTPStreamStats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCInboundRTPStreamStats
RTCInboundRTPStreamStats
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCInboundRTPStreamStats where
  makeObject :: RTCInboundRTPStreamStats -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCInboundRTPStreamStats -> JSVal)
-> RTCInboundRTPStreamStats
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCInboundRTPStreamStats -> JSVal
unRTCInboundRTPStreamStats

instance IsRTCRTPStreamStats RTCInboundRTPStreamStats
instance IsRTCStats RTCInboundRTPStreamStats
instance IsGObject RTCInboundRTPStreamStats where
  typeGType :: RTCInboundRTPStreamStats -> JSM GType
typeGType RTCInboundRTPStreamStats
_ = JSM GType
gTypeRTCInboundRTPStreamStats
  {-# INLINE typeGType #-}

noRTCInboundRTPStreamStats :: Maybe RTCInboundRTPStreamStats
noRTCInboundRTPStreamStats :: Maybe RTCInboundRTPStreamStats
noRTCInboundRTPStreamStats = Maybe RTCInboundRTPStreamStats
forall a. Maybe a
Nothing
{-# INLINE noRTCInboundRTPStreamStats #-}

gTypeRTCInboundRTPStreamStats :: JSM GType
gTypeRTCInboundRTPStreamStats :: JSM GType
gTypeRTCInboundRTPStreamStats = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCInboundRTPStreamStats"

-- | Functions for this inteface are in "JSDOM.RTCMediaStreamTrackStats".
-- Base interface functions are in:
--
--     * "JSDOM.RTCStats"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCMediaStreamTrackStats Mozilla RTCMediaStreamTrackStats documentation>
newtype RTCMediaStreamTrackStats = RTCMediaStreamTrackStats { RTCMediaStreamTrackStats -> JSVal
unRTCMediaStreamTrackStats :: JSVal }

instance PToJSVal RTCMediaStreamTrackStats where
  pToJSVal :: RTCMediaStreamTrackStats -> JSVal
pToJSVal = RTCMediaStreamTrackStats -> JSVal
unRTCMediaStreamTrackStats
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCMediaStreamTrackStats where
  pFromJSVal :: JSVal -> RTCMediaStreamTrackStats
pFromJSVal = JSVal -> RTCMediaStreamTrackStats
RTCMediaStreamTrackStats
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCMediaStreamTrackStats where
  toJSVal :: RTCMediaStreamTrackStats -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCMediaStreamTrackStats -> JSVal)
-> RTCMediaStreamTrackStats
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCMediaStreamTrackStats -> JSVal
unRTCMediaStreamTrackStats
  {-# INLINE toJSVal #-}

instance FromJSVal RTCMediaStreamTrackStats where
  fromJSVal :: JSVal -> JSM (Maybe RTCMediaStreamTrackStats)
fromJSVal JSVal
v = (JSVal -> RTCMediaStreamTrackStats)
-> Maybe JSVal -> Maybe RTCMediaStreamTrackStats
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCMediaStreamTrackStats
RTCMediaStreamTrackStats (Maybe JSVal -> Maybe RTCMediaStreamTrackStats)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCMediaStreamTrackStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCMediaStreamTrackStats
fromJSValUnchecked = RTCMediaStreamTrackStats -> JSM RTCMediaStreamTrackStats
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCMediaStreamTrackStats -> JSM RTCMediaStreamTrackStats)
-> (JSVal -> RTCMediaStreamTrackStats)
-> JSVal
-> JSM RTCMediaStreamTrackStats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCMediaStreamTrackStats
RTCMediaStreamTrackStats
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCMediaStreamTrackStats where
  makeObject :: RTCMediaStreamTrackStats -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCMediaStreamTrackStats -> JSVal)
-> RTCMediaStreamTrackStats
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCMediaStreamTrackStats -> JSVal
unRTCMediaStreamTrackStats

instance IsRTCStats RTCMediaStreamTrackStats
instance IsGObject RTCMediaStreamTrackStats where
  typeGType :: RTCMediaStreamTrackStats -> JSM GType
typeGType RTCMediaStreamTrackStats
_ = JSM GType
gTypeRTCMediaStreamTrackStats
  {-# INLINE typeGType #-}

noRTCMediaStreamTrackStats :: Maybe RTCMediaStreamTrackStats
noRTCMediaStreamTrackStats :: Maybe RTCMediaStreamTrackStats
noRTCMediaStreamTrackStats = Maybe RTCMediaStreamTrackStats
forall a. Maybe a
Nothing
{-# INLINE noRTCMediaStreamTrackStats #-}

gTypeRTCMediaStreamTrackStats :: JSM GType
gTypeRTCMediaStreamTrackStats :: JSM GType
gTypeRTCMediaStreamTrackStats = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCMediaStreamTrackStats"

-- | Functions for this inteface are in "JSDOM.RTCOfferAnswerOptions".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCOfferAnswerOptions Mozilla RTCOfferAnswerOptions documentation>
newtype RTCOfferAnswerOptions = RTCOfferAnswerOptions { RTCOfferAnswerOptions -> JSVal
unRTCOfferAnswerOptions :: JSVal }

instance PToJSVal RTCOfferAnswerOptions where
  pToJSVal :: RTCOfferAnswerOptions -> JSVal
pToJSVal = RTCOfferAnswerOptions -> JSVal
unRTCOfferAnswerOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCOfferAnswerOptions where
  pFromJSVal :: JSVal -> RTCOfferAnswerOptions
pFromJSVal = JSVal -> RTCOfferAnswerOptions
RTCOfferAnswerOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCOfferAnswerOptions where
  toJSVal :: RTCOfferAnswerOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCOfferAnswerOptions -> JSVal)
-> RTCOfferAnswerOptions
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCOfferAnswerOptions -> JSVal
unRTCOfferAnswerOptions
  {-# INLINE toJSVal #-}

instance FromJSVal RTCOfferAnswerOptions where
  fromJSVal :: JSVal -> JSM (Maybe RTCOfferAnswerOptions)
fromJSVal JSVal
v = (JSVal -> RTCOfferAnswerOptions)
-> Maybe JSVal -> Maybe RTCOfferAnswerOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCOfferAnswerOptions
RTCOfferAnswerOptions (Maybe JSVal -> Maybe RTCOfferAnswerOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCOfferAnswerOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCOfferAnswerOptions
fromJSValUnchecked = RTCOfferAnswerOptions -> JSM RTCOfferAnswerOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCOfferAnswerOptions -> JSM RTCOfferAnswerOptions)
-> (JSVal -> RTCOfferAnswerOptions)
-> JSVal
-> JSM RTCOfferAnswerOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCOfferAnswerOptions
RTCOfferAnswerOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCOfferAnswerOptions where
  makeObject :: RTCOfferAnswerOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCOfferAnswerOptions -> JSVal)
-> RTCOfferAnswerOptions
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCOfferAnswerOptions -> JSVal
unRTCOfferAnswerOptions

class (IsGObject o) => IsRTCOfferAnswerOptions o
toRTCOfferAnswerOptions :: IsRTCOfferAnswerOptions o => o -> RTCOfferAnswerOptions
toRTCOfferAnswerOptions :: forall o. IsRTCOfferAnswerOptions o => o -> RTCOfferAnswerOptions
toRTCOfferAnswerOptions = JSVal -> RTCOfferAnswerOptions
RTCOfferAnswerOptions (JSVal -> RTCOfferAnswerOptions)
-> (o -> JSVal) -> o -> RTCOfferAnswerOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsRTCOfferAnswerOptions RTCOfferAnswerOptions
instance IsGObject RTCOfferAnswerOptions where
  typeGType :: RTCOfferAnswerOptions -> JSM GType
typeGType RTCOfferAnswerOptions
_ = JSM GType
gTypeRTCOfferAnswerOptions
  {-# INLINE typeGType #-}

noRTCOfferAnswerOptions :: Maybe RTCOfferAnswerOptions
noRTCOfferAnswerOptions :: Maybe RTCOfferAnswerOptions
noRTCOfferAnswerOptions = Maybe RTCOfferAnswerOptions
forall a. Maybe a
Nothing
{-# INLINE noRTCOfferAnswerOptions #-}

gTypeRTCOfferAnswerOptions :: JSM GType
gTypeRTCOfferAnswerOptions :: JSM GType
gTypeRTCOfferAnswerOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCOfferAnswerOptions"

-- | Functions for this inteface are in "JSDOM.RTCOfferOptions".
-- Base interface functions are in:
--
--     * "JSDOM.RTCOfferAnswerOptions"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCOfferOptions Mozilla RTCOfferOptions documentation>
newtype RTCOfferOptions = RTCOfferOptions { RTCOfferOptions -> JSVal
unRTCOfferOptions :: JSVal }

instance PToJSVal RTCOfferOptions where
  pToJSVal :: RTCOfferOptions -> JSVal
pToJSVal = RTCOfferOptions -> JSVal
unRTCOfferOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCOfferOptions where
  pFromJSVal :: JSVal -> RTCOfferOptions
pFromJSVal = JSVal -> RTCOfferOptions
RTCOfferOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCOfferOptions where
  toJSVal :: RTCOfferOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCOfferOptions -> JSVal) -> RTCOfferOptions -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCOfferOptions -> JSVal
unRTCOfferOptions
  {-# INLINE toJSVal #-}

instance FromJSVal RTCOfferOptions where
  fromJSVal :: JSVal -> JSM (Maybe RTCOfferOptions)
fromJSVal JSVal
v = (JSVal -> RTCOfferOptions) -> Maybe JSVal -> Maybe RTCOfferOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCOfferOptions
RTCOfferOptions (Maybe JSVal -> Maybe RTCOfferOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCOfferOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCOfferOptions
fromJSValUnchecked = RTCOfferOptions -> JSM RTCOfferOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCOfferOptions -> JSM RTCOfferOptions)
-> (JSVal -> RTCOfferOptions) -> JSVal -> JSM RTCOfferOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCOfferOptions
RTCOfferOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCOfferOptions where
  makeObject :: RTCOfferOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCOfferOptions -> JSVal) -> RTCOfferOptions -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCOfferOptions -> JSVal
unRTCOfferOptions

instance IsRTCOfferAnswerOptions RTCOfferOptions
instance IsGObject RTCOfferOptions where
  typeGType :: RTCOfferOptions -> JSM GType
typeGType RTCOfferOptions
_ = JSM GType
gTypeRTCOfferOptions
  {-# INLINE typeGType #-}

noRTCOfferOptions :: Maybe RTCOfferOptions
noRTCOfferOptions :: Maybe RTCOfferOptions
noRTCOfferOptions = Maybe RTCOfferOptions
forall a. Maybe a
Nothing
{-# INLINE noRTCOfferOptions #-}

gTypeRTCOfferOptions :: JSM GType
gTypeRTCOfferOptions :: JSM GType
gTypeRTCOfferOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCOfferOptions"

-- | Functions for this inteface are in "JSDOM.RTCOutboundRTPStreamStats".
-- Base interface functions are in:
--
--     * "JSDOM.RTCRTPStreamStats"
--     * "JSDOM.RTCStats"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCOutboundRTPStreamStats Mozilla RTCOutboundRTPStreamStats documentation>
newtype RTCOutboundRTPStreamStats = RTCOutboundRTPStreamStats { RTCOutboundRTPStreamStats -> JSVal
unRTCOutboundRTPStreamStats :: JSVal }

instance PToJSVal RTCOutboundRTPStreamStats where
  pToJSVal :: RTCOutboundRTPStreamStats -> JSVal
pToJSVal = RTCOutboundRTPStreamStats -> JSVal
unRTCOutboundRTPStreamStats
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCOutboundRTPStreamStats where
  pFromJSVal :: JSVal -> RTCOutboundRTPStreamStats
pFromJSVal = JSVal -> RTCOutboundRTPStreamStats
RTCOutboundRTPStreamStats
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCOutboundRTPStreamStats where
  toJSVal :: RTCOutboundRTPStreamStats -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCOutboundRTPStreamStats -> JSVal)
-> RTCOutboundRTPStreamStats
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCOutboundRTPStreamStats -> JSVal
unRTCOutboundRTPStreamStats
  {-# INLINE toJSVal #-}

instance FromJSVal RTCOutboundRTPStreamStats where
  fromJSVal :: JSVal -> JSM (Maybe RTCOutboundRTPStreamStats)
fromJSVal JSVal
v = (JSVal -> RTCOutboundRTPStreamStats)
-> Maybe JSVal -> Maybe RTCOutboundRTPStreamStats
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCOutboundRTPStreamStats
RTCOutboundRTPStreamStats (Maybe JSVal -> Maybe RTCOutboundRTPStreamStats)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCOutboundRTPStreamStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCOutboundRTPStreamStats
fromJSValUnchecked = RTCOutboundRTPStreamStats -> JSM RTCOutboundRTPStreamStats
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCOutboundRTPStreamStats -> JSM RTCOutboundRTPStreamStats)
-> (JSVal -> RTCOutboundRTPStreamStats)
-> JSVal
-> JSM RTCOutboundRTPStreamStats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCOutboundRTPStreamStats
RTCOutboundRTPStreamStats
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCOutboundRTPStreamStats where
  makeObject :: RTCOutboundRTPStreamStats -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCOutboundRTPStreamStats -> JSVal)
-> RTCOutboundRTPStreamStats
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCOutboundRTPStreamStats -> JSVal
unRTCOutboundRTPStreamStats

instance IsRTCRTPStreamStats RTCOutboundRTPStreamStats
instance IsRTCStats RTCOutboundRTPStreamStats
instance IsGObject RTCOutboundRTPStreamStats where
  typeGType :: RTCOutboundRTPStreamStats -> JSM GType
typeGType RTCOutboundRTPStreamStats
_ = JSM GType
gTypeRTCOutboundRTPStreamStats
  {-# INLINE typeGType #-}

noRTCOutboundRTPStreamStats :: Maybe RTCOutboundRTPStreamStats
noRTCOutboundRTPStreamStats :: Maybe RTCOutboundRTPStreamStats
noRTCOutboundRTPStreamStats = Maybe RTCOutboundRTPStreamStats
forall a. Maybe a
Nothing
{-# INLINE noRTCOutboundRTPStreamStats #-}

gTypeRTCOutboundRTPStreamStats :: JSM GType
gTypeRTCOutboundRTPStreamStats :: JSM GType
gTypeRTCOutboundRTPStreamStats = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCOutboundRTPStreamStats"

-- | Functions for this inteface are in "JSDOM.RTCPeerConnection".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/webkitRTCPeerConnection Mozilla webkitRTCPeerConnection documentation>
newtype RTCPeerConnection = RTCPeerConnection { RTCPeerConnection -> JSVal
unRTCPeerConnection :: JSVal }

instance PToJSVal RTCPeerConnection where
  pToJSVal :: RTCPeerConnection -> JSVal
pToJSVal = RTCPeerConnection -> JSVal
unRTCPeerConnection
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCPeerConnection where
  pFromJSVal :: JSVal -> RTCPeerConnection
pFromJSVal = JSVal -> RTCPeerConnection
RTCPeerConnection
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCPeerConnection where
  toJSVal :: RTCPeerConnection -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCPeerConnection -> JSVal) -> RTCPeerConnection -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCPeerConnection -> JSVal
unRTCPeerConnection
  {-# INLINE toJSVal #-}

instance FromJSVal RTCPeerConnection where
  fromJSVal :: JSVal -> JSM (Maybe RTCPeerConnection)
fromJSVal JSVal
v = (JSVal -> RTCPeerConnection)
-> Maybe JSVal -> Maybe RTCPeerConnection
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCPeerConnection
RTCPeerConnection (Maybe JSVal -> Maybe RTCPeerConnection)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCPeerConnection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCPeerConnection
fromJSValUnchecked = RTCPeerConnection -> JSM RTCPeerConnection
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCPeerConnection -> JSM RTCPeerConnection)
-> (JSVal -> RTCPeerConnection) -> JSVal -> JSM RTCPeerConnection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCPeerConnection
RTCPeerConnection
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCPeerConnection where
  makeObject :: RTCPeerConnection -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCPeerConnection -> JSVal) -> RTCPeerConnection -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCPeerConnection -> JSVal
unRTCPeerConnection

instance IsEventTarget RTCPeerConnection
instance IsGObject RTCPeerConnection where
  typeGType :: RTCPeerConnection -> JSM GType
typeGType RTCPeerConnection
_ = JSM GType
gTypeRTCPeerConnection
  {-# INLINE typeGType #-}

noRTCPeerConnection :: Maybe RTCPeerConnection
noRTCPeerConnection :: Maybe RTCPeerConnection
noRTCPeerConnection = Maybe RTCPeerConnection
forall a. Maybe a
Nothing
{-# INLINE noRTCPeerConnection #-}

gTypeRTCPeerConnection :: JSM GType
gTypeRTCPeerConnection :: JSM GType
gTypeRTCPeerConnection = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"webkitRTCPeerConnection"

-- | Functions for this inteface are in "JSDOM.RTCPeerConnectionIceEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCPeerConnectionIceEvent Mozilla RTCPeerConnectionIceEvent documentation>
newtype RTCPeerConnectionIceEvent = RTCPeerConnectionIceEvent { RTCPeerConnectionIceEvent -> JSVal
unRTCPeerConnectionIceEvent :: JSVal }

instance PToJSVal RTCPeerConnectionIceEvent where
  pToJSVal :: RTCPeerConnectionIceEvent -> JSVal
pToJSVal = RTCPeerConnectionIceEvent -> JSVal
unRTCPeerConnectionIceEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCPeerConnectionIceEvent where
  pFromJSVal :: JSVal -> RTCPeerConnectionIceEvent
pFromJSVal = JSVal -> RTCPeerConnectionIceEvent
RTCPeerConnectionIceEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCPeerConnectionIceEvent where
  toJSVal :: RTCPeerConnectionIceEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCPeerConnectionIceEvent -> JSVal)
-> RTCPeerConnectionIceEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCPeerConnectionIceEvent -> JSVal
unRTCPeerConnectionIceEvent
  {-# INLINE toJSVal #-}

instance FromJSVal RTCPeerConnectionIceEvent where
  fromJSVal :: JSVal -> JSM (Maybe RTCPeerConnectionIceEvent)
fromJSVal JSVal
v = (JSVal -> RTCPeerConnectionIceEvent)
-> Maybe JSVal -> Maybe RTCPeerConnectionIceEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCPeerConnectionIceEvent
RTCPeerConnectionIceEvent (Maybe JSVal -> Maybe RTCPeerConnectionIceEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCPeerConnectionIceEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCPeerConnectionIceEvent
fromJSValUnchecked = RTCPeerConnectionIceEvent -> JSM RTCPeerConnectionIceEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCPeerConnectionIceEvent -> JSM RTCPeerConnectionIceEvent)
-> (JSVal -> RTCPeerConnectionIceEvent)
-> JSVal
-> JSM RTCPeerConnectionIceEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCPeerConnectionIceEvent
RTCPeerConnectionIceEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCPeerConnectionIceEvent where
  makeObject :: RTCPeerConnectionIceEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCPeerConnectionIceEvent -> JSVal)
-> RTCPeerConnectionIceEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCPeerConnectionIceEvent -> JSVal
unRTCPeerConnectionIceEvent

instance IsEvent RTCPeerConnectionIceEvent
instance IsGObject RTCPeerConnectionIceEvent where
  typeGType :: RTCPeerConnectionIceEvent -> JSM GType
typeGType RTCPeerConnectionIceEvent
_ = JSM GType
gTypeRTCPeerConnectionIceEvent
  {-# INLINE typeGType #-}

noRTCPeerConnectionIceEvent :: Maybe RTCPeerConnectionIceEvent
noRTCPeerConnectionIceEvent :: Maybe RTCPeerConnectionIceEvent
noRTCPeerConnectionIceEvent = Maybe RTCPeerConnectionIceEvent
forall a. Maybe a
Nothing
{-# INLINE noRTCPeerConnectionIceEvent #-}

gTypeRTCPeerConnectionIceEvent :: JSM GType
gTypeRTCPeerConnectionIceEvent :: JSM GType
gTypeRTCPeerConnectionIceEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCPeerConnectionIceEvent"

-- | Functions for this inteface are in "JSDOM.RTCRTPStreamStats".
-- Base interface functions are in:
--
--     * "JSDOM.RTCStats"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCRTPStreamStats Mozilla RTCRTPStreamStats documentation>
newtype RTCRTPStreamStats = RTCRTPStreamStats { RTCRTPStreamStats -> JSVal
unRTCRTPStreamStats :: JSVal }

instance PToJSVal RTCRTPStreamStats where
  pToJSVal :: RTCRTPStreamStats -> JSVal
pToJSVal = RTCRTPStreamStats -> JSVal
unRTCRTPStreamStats
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCRTPStreamStats where
  pFromJSVal :: JSVal -> RTCRTPStreamStats
pFromJSVal = JSVal -> RTCRTPStreamStats
RTCRTPStreamStats
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCRTPStreamStats where
  toJSVal :: RTCRTPStreamStats -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCRTPStreamStats -> JSVal) -> RTCRTPStreamStats -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRTPStreamStats -> JSVal
unRTCRTPStreamStats
  {-# INLINE toJSVal #-}

instance FromJSVal RTCRTPStreamStats where
  fromJSVal :: JSVal -> JSM (Maybe RTCRTPStreamStats)
fromJSVal JSVal
v = (JSVal -> RTCRTPStreamStats)
-> Maybe JSVal -> Maybe RTCRTPStreamStats
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCRTPStreamStats
RTCRTPStreamStats (Maybe JSVal -> Maybe RTCRTPStreamStats)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCRTPStreamStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCRTPStreamStats
fromJSValUnchecked = RTCRTPStreamStats -> JSM RTCRTPStreamStats
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRTPStreamStats -> JSM RTCRTPStreamStats)
-> (JSVal -> RTCRTPStreamStats) -> JSVal -> JSM RTCRTPStreamStats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCRTPStreamStats
RTCRTPStreamStats
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCRTPStreamStats where
  makeObject :: RTCRTPStreamStats -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCRTPStreamStats -> JSVal) -> RTCRTPStreamStats -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRTPStreamStats -> JSVal
unRTCRTPStreamStats

class (IsRTCStats o, IsGObject o) => IsRTCRTPStreamStats o
toRTCRTPStreamStats :: IsRTCRTPStreamStats o => o -> RTCRTPStreamStats
toRTCRTPStreamStats :: forall o. IsRTCRTPStreamStats o => o -> RTCRTPStreamStats
toRTCRTPStreamStats = JSVal -> RTCRTPStreamStats
RTCRTPStreamStats (JSVal -> RTCRTPStreamStats)
-> (o -> JSVal) -> o -> RTCRTPStreamStats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsRTCRTPStreamStats RTCRTPStreamStats
instance IsRTCStats RTCRTPStreamStats
instance IsGObject RTCRTPStreamStats where
  typeGType :: RTCRTPStreamStats -> JSM GType
typeGType RTCRTPStreamStats
_ = JSM GType
gTypeRTCRTPStreamStats
  {-# INLINE typeGType #-}

noRTCRTPStreamStats :: Maybe RTCRTPStreamStats
noRTCRTPStreamStats :: Maybe RTCRTPStreamStats
noRTCRTPStreamStats = Maybe RTCRTPStreamStats
forall a. Maybe a
Nothing
{-# INLINE noRTCRTPStreamStats #-}

gTypeRTCRTPStreamStats :: JSM GType
gTypeRTCRTPStreamStats :: JSM GType
gTypeRTCRTPStreamStats = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCRTPStreamStats"

-- | Functions for this inteface are in "JSDOM.RTCRtpCodecParameters".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCRtpCodecParameters Mozilla RTCRtpCodecParameters documentation>
newtype RTCRtpCodecParameters = RTCRtpCodecParameters { RTCRtpCodecParameters -> JSVal
unRTCRtpCodecParameters :: JSVal }

instance PToJSVal RTCRtpCodecParameters where
  pToJSVal :: RTCRtpCodecParameters -> JSVal
pToJSVal = RTCRtpCodecParameters -> JSVal
unRTCRtpCodecParameters
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCRtpCodecParameters where
  pFromJSVal :: JSVal -> RTCRtpCodecParameters
pFromJSVal = JSVal -> RTCRtpCodecParameters
RTCRtpCodecParameters
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCRtpCodecParameters where
  toJSVal :: RTCRtpCodecParameters -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCRtpCodecParameters -> JSVal)
-> RTCRtpCodecParameters
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpCodecParameters -> JSVal
unRTCRtpCodecParameters
  {-# INLINE toJSVal #-}

instance FromJSVal RTCRtpCodecParameters where
  fromJSVal :: JSVal -> JSM (Maybe RTCRtpCodecParameters)
fromJSVal JSVal
v = (JSVal -> RTCRtpCodecParameters)
-> Maybe JSVal -> Maybe RTCRtpCodecParameters
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCRtpCodecParameters
RTCRtpCodecParameters (Maybe JSVal -> Maybe RTCRtpCodecParameters)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCRtpCodecParameters)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCRtpCodecParameters
fromJSValUnchecked = RTCRtpCodecParameters -> JSM RTCRtpCodecParameters
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpCodecParameters -> JSM RTCRtpCodecParameters)
-> (JSVal -> RTCRtpCodecParameters)
-> JSVal
-> JSM RTCRtpCodecParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCRtpCodecParameters
RTCRtpCodecParameters
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCRtpCodecParameters where
  makeObject :: RTCRtpCodecParameters -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCRtpCodecParameters -> JSVal)
-> RTCRtpCodecParameters
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpCodecParameters -> JSVal
unRTCRtpCodecParameters

instance IsGObject RTCRtpCodecParameters where
  typeGType :: RTCRtpCodecParameters -> JSM GType
typeGType RTCRtpCodecParameters
_ = JSM GType
gTypeRTCRtpCodecParameters
  {-# INLINE typeGType #-}

noRTCRtpCodecParameters :: Maybe RTCRtpCodecParameters
noRTCRtpCodecParameters :: Maybe RTCRtpCodecParameters
noRTCRtpCodecParameters = Maybe RTCRtpCodecParameters
forall a. Maybe a
Nothing
{-# INLINE noRTCRtpCodecParameters #-}

gTypeRTCRtpCodecParameters :: JSM GType
gTypeRTCRtpCodecParameters :: JSM GType
gTypeRTCRtpCodecParameters = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCRtpCodecParameters"

-- | Functions for this inteface are in "JSDOM.RTCRtpEncodingParameters".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCRtpEncodingParameters Mozilla RTCRtpEncodingParameters documentation>
newtype RTCRtpEncodingParameters = RTCRtpEncodingParameters { RTCRtpEncodingParameters -> JSVal
unRTCRtpEncodingParameters :: JSVal }

instance PToJSVal RTCRtpEncodingParameters where
  pToJSVal :: RTCRtpEncodingParameters -> JSVal
pToJSVal = RTCRtpEncodingParameters -> JSVal
unRTCRtpEncodingParameters
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCRtpEncodingParameters where
  pFromJSVal :: JSVal -> RTCRtpEncodingParameters
pFromJSVal = JSVal -> RTCRtpEncodingParameters
RTCRtpEncodingParameters
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCRtpEncodingParameters where
  toJSVal :: RTCRtpEncodingParameters -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCRtpEncodingParameters -> JSVal)
-> RTCRtpEncodingParameters
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpEncodingParameters -> JSVal
unRTCRtpEncodingParameters
  {-# INLINE toJSVal #-}

instance FromJSVal RTCRtpEncodingParameters where
  fromJSVal :: JSVal -> JSM (Maybe RTCRtpEncodingParameters)
fromJSVal JSVal
v = (JSVal -> RTCRtpEncodingParameters)
-> Maybe JSVal -> Maybe RTCRtpEncodingParameters
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCRtpEncodingParameters
RTCRtpEncodingParameters (Maybe JSVal -> Maybe RTCRtpEncodingParameters)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCRtpEncodingParameters)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCRtpEncodingParameters
fromJSValUnchecked = RTCRtpEncodingParameters -> JSM RTCRtpEncodingParameters
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpEncodingParameters -> JSM RTCRtpEncodingParameters)
-> (JSVal -> RTCRtpEncodingParameters)
-> JSVal
-> JSM RTCRtpEncodingParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCRtpEncodingParameters
RTCRtpEncodingParameters
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCRtpEncodingParameters where
  makeObject :: RTCRtpEncodingParameters -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCRtpEncodingParameters -> JSVal)
-> RTCRtpEncodingParameters
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpEncodingParameters -> JSVal
unRTCRtpEncodingParameters

instance IsGObject RTCRtpEncodingParameters where
  typeGType :: RTCRtpEncodingParameters -> JSM GType
typeGType RTCRtpEncodingParameters
_ = JSM GType
gTypeRTCRtpEncodingParameters
  {-# INLINE typeGType #-}

noRTCRtpEncodingParameters :: Maybe RTCRtpEncodingParameters
noRTCRtpEncodingParameters :: Maybe RTCRtpEncodingParameters
noRTCRtpEncodingParameters = Maybe RTCRtpEncodingParameters
forall a. Maybe a
Nothing
{-# INLINE noRTCRtpEncodingParameters #-}

gTypeRTCRtpEncodingParameters :: JSM GType
gTypeRTCRtpEncodingParameters :: JSM GType
gTypeRTCRtpEncodingParameters = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCRtpEncodingParameters"

-- | Functions for this inteface are in "JSDOM.RTCRtpFecParameters".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCRtpFecParameters Mozilla RTCRtpFecParameters documentation>
newtype RTCRtpFecParameters = RTCRtpFecParameters { RTCRtpFecParameters -> JSVal
unRTCRtpFecParameters :: JSVal }

instance PToJSVal RTCRtpFecParameters where
  pToJSVal :: RTCRtpFecParameters -> JSVal
pToJSVal = RTCRtpFecParameters -> JSVal
unRTCRtpFecParameters
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCRtpFecParameters where
  pFromJSVal :: JSVal -> RTCRtpFecParameters
pFromJSVal = JSVal -> RTCRtpFecParameters
RTCRtpFecParameters
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCRtpFecParameters where
  toJSVal :: RTCRtpFecParameters -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCRtpFecParameters -> JSVal)
-> RTCRtpFecParameters
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpFecParameters -> JSVal
unRTCRtpFecParameters
  {-# INLINE toJSVal #-}

instance FromJSVal RTCRtpFecParameters where
  fromJSVal :: JSVal -> JSM (Maybe RTCRtpFecParameters)
fromJSVal JSVal
v = (JSVal -> RTCRtpFecParameters)
-> Maybe JSVal -> Maybe RTCRtpFecParameters
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCRtpFecParameters
RTCRtpFecParameters (Maybe JSVal -> Maybe RTCRtpFecParameters)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCRtpFecParameters)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCRtpFecParameters
fromJSValUnchecked = RTCRtpFecParameters -> JSM RTCRtpFecParameters
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpFecParameters -> JSM RTCRtpFecParameters)
-> (JSVal -> RTCRtpFecParameters)
-> JSVal
-> JSM RTCRtpFecParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCRtpFecParameters
RTCRtpFecParameters
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCRtpFecParameters where
  makeObject :: RTCRtpFecParameters -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCRtpFecParameters -> JSVal)
-> RTCRtpFecParameters
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpFecParameters -> JSVal
unRTCRtpFecParameters

instance IsGObject RTCRtpFecParameters where
  typeGType :: RTCRtpFecParameters -> JSM GType
typeGType RTCRtpFecParameters
_ = JSM GType
gTypeRTCRtpFecParameters
  {-# INLINE typeGType #-}

noRTCRtpFecParameters :: Maybe RTCRtpFecParameters
noRTCRtpFecParameters :: Maybe RTCRtpFecParameters
noRTCRtpFecParameters = Maybe RTCRtpFecParameters
forall a. Maybe a
Nothing
{-# INLINE noRTCRtpFecParameters #-}

gTypeRTCRtpFecParameters :: JSM GType
gTypeRTCRtpFecParameters :: JSM GType
gTypeRTCRtpFecParameters = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCRtpFecParameters"

-- | Functions for this inteface are in "JSDOM.RTCRtpHeaderExtensionParameters".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCRtpHeaderExtensionParameters Mozilla RTCRtpHeaderExtensionParameters documentation>
newtype RTCRtpHeaderExtensionParameters = RTCRtpHeaderExtensionParameters { RTCRtpHeaderExtensionParameters -> JSVal
unRTCRtpHeaderExtensionParameters :: JSVal }

instance PToJSVal RTCRtpHeaderExtensionParameters where
  pToJSVal :: RTCRtpHeaderExtensionParameters -> JSVal
pToJSVal = RTCRtpHeaderExtensionParameters -> JSVal
unRTCRtpHeaderExtensionParameters
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCRtpHeaderExtensionParameters where
  pFromJSVal :: JSVal -> RTCRtpHeaderExtensionParameters
pFromJSVal = JSVal -> RTCRtpHeaderExtensionParameters
RTCRtpHeaderExtensionParameters
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCRtpHeaderExtensionParameters where
  toJSVal :: RTCRtpHeaderExtensionParameters -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCRtpHeaderExtensionParameters -> JSVal)
-> RTCRtpHeaderExtensionParameters
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpHeaderExtensionParameters -> JSVal
unRTCRtpHeaderExtensionParameters
  {-# INLINE toJSVal #-}

instance FromJSVal RTCRtpHeaderExtensionParameters where
  fromJSVal :: JSVal -> JSM (Maybe RTCRtpHeaderExtensionParameters)
fromJSVal JSVal
v = (JSVal -> RTCRtpHeaderExtensionParameters)
-> Maybe JSVal -> Maybe RTCRtpHeaderExtensionParameters
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCRtpHeaderExtensionParameters
RTCRtpHeaderExtensionParameters (Maybe JSVal -> Maybe RTCRtpHeaderExtensionParameters)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCRtpHeaderExtensionParameters)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCRtpHeaderExtensionParameters
fromJSValUnchecked = RTCRtpHeaderExtensionParameters
-> JSM RTCRtpHeaderExtensionParameters
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpHeaderExtensionParameters
 -> JSM RTCRtpHeaderExtensionParameters)
-> (JSVal -> RTCRtpHeaderExtensionParameters)
-> JSVal
-> JSM RTCRtpHeaderExtensionParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCRtpHeaderExtensionParameters
RTCRtpHeaderExtensionParameters
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCRtpHeaderExtensionParameters where
  makeObject :: RTCRtpHeaderExtensionParameters -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCRtpHeaderExtensionParameters -> JSVal)
-> RTCRtpHeaderExtensionParameters
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpHeaderExtensionParameters -> JSVal
unRTCRtpHeaderExtensionParameters

instance IsGObject RTCRtpHeaderExtensionParameters where
  typeGType :: RTCRtpHeaderExtensionParameters -> JSM GType
typeGType RTCRtpHeaderExtensionParameters
_ = JSM GType
gTypeRTCRtpHeaderExtensionParameters
  {-# INLINE typeGType #-}

noRTCRtpHeaderExtensionParameters :: Maybe RTCRtpHeaderExtensionParameters
noRTCRtpHeaderExtensionParameters :: Maybe RTCRtpHeaderExtensionParameters
noRTCRtpHeaderExtensionParameters = Maybe RTCRtpHeaderExtensionParameters
forall a. Maybe a
Nothing
{-# INLINE noRTCRtpHeaderExtensionParameters #-}

gTypeRTCRtpHeaderExtensionParameters :: JSM GType
gTypeRTCRtpHeaderExtensionParameters :: JSM GType
gTypeRTCRtpHeaderExtensionParameters = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCRtpHeaderExtensionParameters"

-- | Functions for this inteface are in "JSDOM.RTCRtpParameters".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCRtpParameters Mozilla RTCRtpParameters documentation>
newtype RTCRtpParameters = RTCRtpParameters { RTCRtpParameters -> JSVal
unRTCRtpParameters :: JSVal }

instance PToJSVal RTCRtpParameters where
  pToJSVal :: RTCRtpParameters -> JSVal
pToJSVal = RTCRtpParameters -> JSVal
unRTCRtpParameters
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCRtpParameters where
  pFromJSVal :: JSVal -> RTCRtpParameters
pFromJSVal = JSVal -> RTCRtpParameters
RTCRtpParameters
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCRtpParameters where
  toJSVal :: RTCRtpParameters -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCRtpParameters -> JSVal) -> RTCRtpParameters -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpParameters -> JSVal
unRTCRtpParameters
  {-# INLINE toJSVal #-}

instance FromJSVal RTCRtpParameters where
  fromJSVal :: JSVal -> JSM (Maybe RTCRtpParameters)
fromJSVal JSVal
v = (JSVal -> RTCRtpParameters)
-> Maybe JSVal -> Maybe RTCRtpParameters
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCRtpParameters
RTCRtpParameters (Maybe JSVal -> Maybe RTCRtpParameters)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCRtpParameters)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCRtpParameters
fromJSValUnchecked = RTCRtpParameters -> JSM RTCRtpParameters
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpParameters -> JSM RTCRtpParameters)
-> (JSVal -> RTCRtpParameters) -> JSVal -> JSM RTCRtpParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCRtpParameters
RTCRtpParameters
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCRtpParameters where
  makeObject :: RTCRtpParameters -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCRtpParameters -> JSVal) -> RTCRtpParameters -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpParameters -> JSVal
unRTCRtpParameters

instance IsGObject RTCRtpParameters where
  typeGType :: RTCRtpParameters -> JSM GType
typeGType RTCRtpParameters
_ = JSM GType
gTypeRTCRtpParameters
  {-# INLINE typeGType #-}

noRTCRtpParameters :: Maybe RTCRtpParameters
noRTCRtpParameters :: Maybe RTCRtpParameters
noRTCRtpParameters = Maybe RTCRtpParameters
forall a. Maybe a
Nothing
{-# INLINE noRTCRtpParameters #-}

gTypeRTCRtpParameters :: JSM GType
gTypeRTCRtpParameters :: JSM GType
gTypeRTCRtpParameters = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCRtpParameters"

-- | Functions for this inteface are in "JSDOM.RTCRtpReceiver".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCRtpReceiver Mozilla RTCRtpReceiver documentation>
newtype RTCRtpReceiver = RTCRtpReceiver { RTCRtpReceiver -> JSVal
unRTCRtpReceiver :: JSVal }

instance PToJSVal RTCRtpReceiver where
  pToJSVal :: RTCRtpReceiver -> JSVal
pToJSVal = RTCRtpReceiver -> JSVal
unRTCRtpReceiver
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCRtpReceiver where
  pFromJSVal :: JSVal -> RTCRtpReceiver
pFromJSVal = JSVal -> RTCRtpReceiver
RTCRtpReceiver
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCRtpReceiver where
  toJSVal :: RTCRtpReceiver -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCRtpReceiver -> JSVal) -> RTCRtpReceiver -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpReceiver -> JSVal
unRTCRtpReceiver
  {-# INLINE toJSVal #-}

instance FromJSVal RTCRtpReceiver where
  fromJSVal :: JSVal -> JSM (Maybe RTCRtpReceiver)
fromJSVal JSVal
v = (JSVal -> RTCRtpReceiver) -> Maybe JSVal -> Maybe RTCRtpReceiver
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCRtpReceiver
RTCRtpReceiver (Maybe JSVal -> Maybe RTCRtpReceiver)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCRtpReceiver)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCRtpReceiver
fromJSValUnchecked = RTCRtpReceiver -> JSM RTCRtpReceiver
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpReceiver -> JSM RTCRtpReceiver)
-> (JSVal -> RTCRtpReceiver) -> JSVal -> JSM RTCRtpReceiver
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCRtpReceiver
RTCRtpReceiver
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCRtpReceiver where
  makeObject :: RTCRtpReceiver -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCRtpReceiver -> JSVal) -> RTCRtpReceiver -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpReceiver -> JSVal
unRTCRtpReceiver

instance IsGObject RTCRtpReceiver where
  typeGType :: RTCRtpReceiver -> JSM GType
typeGType RTCRtpReceiver
_ = JSM GType
gTypeRTCRtpReceiver
  {-# INLINE typeGType #-}

noRTCRtpReceiver :: Maybe RTCRtpReceiver
noRTCRtpReceiver :: Maybe RTCRtpReceiver
noRTCRtpReceiver = Maybe RTCRtpReceiver
forall a. Maybe a
Nothing
{-# INLINE noRTCRtpReceiver #-}

gTypeRTCRtpReceiver :: JSM GType
gTypeRTCRtpReceiver :: JSM GType
gTypeRTCRtpReceiver = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCRtpReceiver"

-- | Functions for this inteface are in "JSDOM.RTCRtpRtxParameters".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCRtpRtxParameters Mozilla RTCRtpRtxParameters documentation>
newtype RTCRtpRtxParameters = RTCRtpRtxParameters { RTCRtpRtxParameters -> JSVal
unRTCRtpRtxParameters :: JSVal }

instance PToJSVal RTCRtpRtxParameters where
  pToJSVal :: RTCRtpRtxParameters -> JSVal
pToJSVal = RTCRtpRtxParameters -> JSVal
unRTCRtpRtxParameters
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCRtpRtxParameters where
  pFromJSVal :: JSVal -> RTCRtpRtxParameters
pFromJSVal = JSVal -> RTCRtpRtxParameters
RTCRtpRtxParameters
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCRtpRtxParameters where
  toJSVal :: RTCRtpRtxParameters -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCRtpRtxParameters -> JSVal)
-> RTCRtpRtxParameters
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpRtxParameters -> JSVal
unRTCRtpRtxParameters
  {-# INLINE toJSVal #-}

instance FromJSVal RTCRtpRtxParameters where
  fromJSVal :: JSVal -> JSM (Maybe RTCRtpRtxParameters)
fromJSVal JSVal
v = (JSVal -> RTCRtpRtxParameters)
-> Maybe JSVal -> Maybe RTCRtpRtxParameters
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCRtpRtxParameters
RTCRtpRtxParameters (Maybe JSVal -> Maybe RTCRtpRtxParameters)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCRtpRtxParameters)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCRtpRtxParameters
fromJSValUnchecked = RTCRtpRtxParameters -> JSM RTCRtpRtxParameters
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpRtxParameters -> JSM RTCRtpRtxParameters)
-> (JSVal -> RTCRtpRtxParameters)
-> JSVal
-> JSM RTCRtpRtxParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCRtpRtxParameters
RTCRtpRtxParameters
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCRtpRtxParameters where
  makeObject :: RTCRtpRtxParameters -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCRtpRtxParameters -> JSVal)
-> RTCRtpRtxParameters
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpRtxParameters -> JSVal
unRTCRtpRtxParameters

instance IsGObject RTCRtpRtxParameters where
  typeGType :: RTCRtpRtxParameters -> JSM GType
typeGType RTCRtpRtxParameters
_ = JSM GType
gTypeRTCRtpRtxParameters
  {-# INLINE typeGType #-}

noRTCRtpRtxParameters :: Maybe RTCRtpRtxParameters
noRTCRtpRtxParameters :: Maybe RTCRtpRtxParameters
noRTCRtpRtxParameters = Maybe RTCRtpRtxParameters
forall a. Maybe a
Nothing
{-# INLINE noRTCRtpRtxParameters #-}

gTypeRTCRtpRtxParameters :: JSM GType
gTypeRTCRtpRtxParameters :: JSM GType
gTypeRTCRtpRtxParameters = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCRtpRtxParameters"

-- | Functions for this inteface are in "JSDOM.RTCRtpSender".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCRtpSender Mozilla RTCRtpSender documentation>
newtype RTCRtpSender = RTCRtpSender { RTCRtpSender -> JSVal
unRTCRtpSender :: JSVal }

instance PToJSVal RTCRtpSender where
  pToJSVal :: RTCRtpSender -> JSVal
pToJSVal = RTCRtpSender -> JSVal
unRTCRtpSender
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCRtpSender where
  pFromJSVal :: JSVal -> RTCRtpSender
pFromJSVal = JSVal -> RTCRtpSender
RTCRtpSender
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCRtpSender where
  toJSVal :: RTCRtpSender -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCRtpSender -> JSVal) -> RTCRtpSender -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpSender -> JSVal
unRTCRtpSender
  {-# INLINE toJSVal #-}

instance FromJSVal RTCRtpSender where
  fromJSVal :: JSVal -> JSM (Maybe RTCRtpSender)
fromJSVal JSVal
v = (JSVal -> RTCRtpSender) -> Maybe JSVal -> Maybe RTCRtpSender
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCRtpSender
RTCRtpSender (Maybe JSVal -> Maybe RTCRtpSender)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCRtpSender)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCRtpSender
fromJSValUnchecked = RTCRtpSender -> JSM RTCRtpSender
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpSender -> JSM RTCRtpSender)
-> (JSVal -> RTCRtpSender) -> JSVal -> JSM RTCRtpSender
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCRtpSender
RTCRtpSender
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCRtpSender where
  makeObject :: RTCRtpSender -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCRtpSender -> JSVal) -> RTCRtpSender -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpSender -> JSVal
unRTCRtpSender

instance IsGObject RTCRtpSender where
  typeGType :: RTCRtpSender -> JSM GType
typeGType RTCRtpSender
_ = JSM GType
gTypeRTCRtpSender
  {-# INLINE typeGType #-}

noRTCRtpSender :: Maybe RTCRtpSender
noRTCRtpSender :: Maybe RTCRtpSender
noRTCRtpSender = Maybe RTCRtpSender
forall a. Maybe a
Nothing
{-# INLINE noRTCRtpSender #-}

gTypeRTCRtpSender :: JSM GType
gTypeRTCRtpSender :: JSM GType
gTypeRTCRtpSender = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCRtpSender"

-- | Functions for this inteface are in "JSDOM.RTCRtpTransceiver".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCRtpTransceiver Mozilla RTCRtpTransceiver documentation>
newtype RTCRtpTransceiver = RTCRtpTransceiver { RTCRtpTransceiver -> JSVal
unRTCRtpTransceiver :: JSVal }

instance PToJSVal RTCRtpTransceiver where
  pToJSVal :: RTCRtpTransceiver -> JSVal
pToJSVal = RTCRtpTransceiver -> JSVal
unRTCRtpTransceiver
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCRtpTransceiver where
  pFromJSVal :: JSVal -> RTCRtpTransceiver
pFromJSVal = JSVal -> RTCRtpTransceiver
RTCRtpTransceiver
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCRtpTransceiver where
  toJSVal :: RTCRtpTransceiver -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCRtpTransceiver -> JSVal) -> RTCRtpTransceiver -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpTransceiver -> JSVal
unRTCRtpTransceiver
  {-# INLINE toJSVal #-}

instance FromJSVal RTCRtpTransceiver where
  fromJSVal :: JSVal -> JSM (Maybe RTCRtpTransceiver)
fromJSVal JSVal
v = (JSVal -> RTCRtpTransceiver)
-> Maybe JSVal -> Maybe RTCRtpTransceiver
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCRtpTransceiver
RTCRtpTransceiver (Maybe JSVal -> Maybe RTCRtpTransceiver)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCRtpTransceiver)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCRtpTransceiver
fromJSValUnchecked = RTCRtpTransceiver -> JSM RTCRtpTransceiver
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpTransceiver -> JSM RTCRtpTransceiver)
-> (JSVal -> RTCRtpTransceiver) -> JSVal -> JSM RTCRtpTransceiver
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCRtpTransceiver
RTCRtpTransceiver
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCRtpTransceiver where
  makeObject :: RTCRtpTransceiver -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCRtpTransceiver -> JSVal) -> RTCRtpTransceiver -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpTransceiver -> JSVal
unRTCRtpTransceiver

instance IsGObject RTCRtpTransceiver where
  typeGType :: RTCRtpTransceiver -> JSM GType
typeGType RTCRtpTransceiver
_ = JSM GType
gTypeRTCRtpTransceiver
  {-# INLINE typeGType #-}

noRTCRtpTransceiver :: Maybe RTCRtpTransceiver
noRTCRtpTransceiver :: Maybe RTCRtpTransceiver
noRTCRtpTransceiver = Maybe RTCRtpTransceiver
forall a. Maybe a
Nothing
{-# INLINE noRTCRtpTransceiver #-}

gTypeRTCRtpTransceiver :: JSM GType
gTypeRTCRtpTransceiver :: JSM GType
gTypeRTCRtpTransceiver = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCRtpTransceiver"

-- | Functions for this inteface are in "JSDOM.RTCRtpTransceiverInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCRtpTransceiverInit Mozilla RTCRtpTransceiverInit documentation>
newtype RTCRtpTransceiverInit = RTCRtpTransceiverInit { RTCRtpTransceiverInit -> JSVal
unRTCRtpTransceiverInit :: JSVal }

instance PToJSVal RTCRtpTransceiverInit where
  pToJSVal :: RTCRtpTransceiverInit -> JSVal
pToJSVal = RTCRtpTransceiverInit -> JSVal
unRTCRtpTransceiverInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCRtpTransceiverInit where
  pFromJSVal :: JSVal -> RTCRtpTransceiverInit
pFromJSVal = JSVal -> RTCRtpTransceiverInit
RTCRtpTransceiverInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCRtpTransceiverInit where
  toJSVal :: RTCRtpTransceiverInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCRtpTransceiverInit -> JSVal)
-> RTCRtpTransceiverInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpTransceiverInit -> JSVal
unRTCRtpTransceiverInit
  {-# INLINE toJSVal #-}

instance FromJSVal RTCRtpTransceiverInit where
  fromJSVal :: JSVal -> JSM (Maybe RTCRtpTransceiverInit)
fromJSVal JSVal
v = (JSVal -> RTCRtpTransceiverInit)
-> Maybe JSVal -> Maybe RTCRtpTransceiverInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCRtpTransceiverInit
RTCRtpTransceiverInit (Maybe JSVal -> Maybe RTCRtpTransceiverInit)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCRtpTransceiverInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCRtpTransceiverInit
fromJSValUnchecked = RTCRtpTransceiverInit -> JSM RTCRtpTransceiverInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpTransceiverInit -> JSM RTCRtpTransceiverInit)
-> (JSVal -> RTCRtpTransceiverInit)
-> JSVal
-> JSM RTCRtpTransceiverInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCRtpTransceiverInit
RTCRtpTransceiverInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCRtpTransceiverInit where
  makeObject :: RTCRtpTransceiverInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCRtpTransceiverInit -> JSVal)
-> RTCRtpTransceiverInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCRtpTransceiverInit -> JSVal
unRTCRtpTransceiverInit

instance IsGObject RTCRtpTransceiverInit where
  typeGType :: RTCRtpTransceiverInit -> JSM GType
typeGType RTCRtpTransceiverInit
_ = JSM GType
gTypeRTCRtpTransceiverInit
  {-# INLINE typeGType #-}

noRTCRtpTransceiverInit :: Maybe RTCRtpTransceiverInit
noRTCRtpTransceiverInit :: Maybe RTCRtpTransceiverInit
noRTCRtpTransceiverInit = Maybe RTCRtpTransceiverInit
forall a. Maybe a
Nothing
{-# INLINE noRTCRtpTransceiverInit #-}

gTypeRTCRtpTransceiverInit :: JSM GType
gTypeRTCRtpTransceiverInit :: JSM GType
gTypeRTCRtpTransceiverInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCRtpTransceiverInit"

-- | Functions for this inteface are in "JSDOM.RTCSessionDescription".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCSessionDescription Mozilla RTCSessionDescription documentation>
newtype RTCSessionDescription = RTCSessionDescription { RTCSessionDescription -> JSVal
unRTCSessionDescription :: JSVal }

instance PToJSVal RTCSessionDescription where
  pToJSVal :: RTCSessionDescription -> JSVal
pToJSVal = RTCSessionDescription -> JSVal
unRTCSessionDescription
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCSessionDescription where
  pFromJSVal :: JSVal -> RTCSessionDescription
pFromJSVal = JSVal -> RTCSessionDescription
RTCSessionDescription
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCSessionDescription where
  toJSVal :: RTCSessionDescription -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCSessionDescription -> JSVal)
-> RTCSessionDescription
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCSessionDescription -> JSVal
unRTCSessionDescription
  {-# INLINE toJSVal #-}

instance FromJSVal RTCSessionDescription where
  fromJSVal :: JSVal -> JSM (Maybe RTCSessionDescription)
fromJSVal JSVal
v = (JSVal -> RTCSessionDescription)
-> Maybe JSVal -> Maybe RTCSessionDescription
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCSessionDescription
RTCSessionDescription (Maybe JSVal -> Maybe RTCSessionDescription)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCSessionDescription)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCSessionDescription
fromJSValUnchecked = RTCSessionDescription -> JSM RTCSessionDescription
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCSessionDescription -> JSM RTCSessionDescription)
-> (JSVal -> RTCSessionDescription)
-> JSVal
-> JSM RTCSessionDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCSessionDescription
RTCSessionDescription
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCSessionDescription where
  makeObject :: RTCSessionDescription -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCSessionDescription -> JSVal)
-> RTCSessionDescription
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCSessionDescription -> JSVal
unRTCSessionDescription

instance IsGObject RTCSessionDescription where
  typeGType :: RTCSessionDescription -> JSM GType
typeGType RTCSessionDescription
_ = JSM GType
gTypeRTCSessionDescription
  {-# INLINE typeGType #-}

noRTCSessionDescription :: Maybe RTCSessionDescription
noRTCSessionDescription :: Maybe RTCSessionDescription
noRTCSessionDescription = Maybe RTCSessionDescription
forall a. Maybe a
Nothing
{-# INLINE noRTCSessionDescription #-}

gTypeRTCSessionDescription :: JSM GType
gTypeRTCSessionDescription :: JSM GType
gTypeRTCSessionDescription = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCSessionDescription"

-- | Functions for this inteface are in "JSDOM.RTCSessionDescriptionInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCSessionDescriptionInit Mozilla RTCSessionDescriptionInit documentation>
newtype RTCSessionDescriptionInit = RTCSessionDescriptionInit { RTCSessionDescriptionInit -> JSVal
unRTCSessionDescriptionInit :: JSVal }

instance PToJSVal RTCSessionDescriptionInit where
  pToJSVal :: RTCSessionDescriptionInit -> JSVal
pToJSVal = RTCSessionDescriptionInit -> JSVal
unRTCSessionDescriptionInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCSessionDescriptionInit where
  pFromJSVal :: JSVal -> RTCSessionDescriptionInit
pFromJSVal = JSVal -> RTCSessionDescriptionInit
RTCSessionDescriptionInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCSessionDescriptionInit where
  toJSVal :: RTCSessionDescriptionInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCSessionDescriptionInit -> JSVal)
-> RTCSessionDescriptionInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCSessionDescriptionInit -> JSVal
unRTCSessionDescriptionInit
  {-# INLINE toJSVal #-}

instance FromJSVal RTCSessionDescriptionInit where
  fromJSVal :: JSVal -> JSM (Maybe RTCSessionDescriptionInit)
fromJSVal JSVal
v = (JSVal -> RTCSessionDescriptionInit)
-> Maybe JSVal -> Maybe RTCSessionDescriptionInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCSessionDescriptionInit
RTCSessionDescriptionInit (Maybe JSVal -> Maybe RTCSessionDescriptionInit)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCSessionDescriptionInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCSessionDescriptionInit
fromJSValUnchecked = RTCSessionDescriptionInit -> JSM RTCSessionDescriptionInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCSessionDescriptionInit -> JSM RTCSessionDescriptionInit)
-> (JSVal -> RTCSessionDescriptionInit)
-> JSVal
-> JSM RTCSessionDescriptionInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCSessionDescriptionInit
RTCSessionDescriptionInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCSessionDescriptionInit where
  makeObject :: RTCSessionDescriptionInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCSessionDescriptionInit -> JSVal)
-> RTCSessionDescriptionInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCSessionDescriptionInit -> JSVal
unRTCSessionDescriptionInit

instance IsGObject RTCSessionDescriptionInit where
  typeGType :: RTCSessionDescriptionInit -> JSM GType
typeGType RTCSessionDescriptionInit
_ = JSM GType
gTypeRTCSessionDescriptionInit
  {-# INLINE typeGType #-}

noRTCSessionDescriptionInit :: Maybe RTCSessionDescriptionInit
noRTCSessionDescriptionInit :: Maybe RTCSessionDescriptionInit
noRTCSessionDescriptionInit = Maybe RTCSessionDescriptionInit
forall a. Maybe a
Nothing
{-# INLINE noRTCSessionDescriptionInit #-}

gTypeRTCSessionDescriptionInit :: JSM GType
gTypeRTCSessionDescriptionInit :: JSM GType
gTypeRTCSessionDescriptionInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCSessionDescriptionInit"

-- | Functions for this inteface are in "JSDOM.RTCStats".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCStats Mozilla RTCStats documentation>
newtype RTCStats = RTCStats { RTCStats -> JSVal
unRTCStats :: JSVal }

instance PToJSVal RTCStats where
  pToJSVal :: RTCStats -> JSVal
pToJSVal = RTCStats -> JSVal
unRTCStats
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCStats where
  pFromJSVal :: JSVal -> RTCStats
pFromJSVal = JSVal -> RTCStats
RTCStats
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCStats where
  toJSVal :: RTCStats -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCStats -> JSVal) -> RTCStats -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCStats -> JSVal
unRTCStats
  {-# INLINE toJSVal #-}

instance FromJSVal RTCStats where
  fromJSVal :: JSVal -> JSM (Maybe RTCStats)
fromJSVal JSVal
v = (JSVal -> RTCStats) -> Maybe JSVal -> Maybe RTCStats
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCStats
RTCStats (Maybe JSVal -> Maybe RTCStats)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCStats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCStats
fromJSValUnchecked = RTCStats -> JSM RTCStats
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCStats -> JSM RTCStats)
-> (JSVal -> RTCStats) -> JSVal -> JSM RTCStats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCStats
RTCStats
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCStats where
  makeObject :: RTCStats -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCStats -> JSVal) -> RTCStats -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCStats -> JSVal
unRTCStats

class (IsGObject o) => IsRTCStats o
toRTCStats :: IsRTCStats o => o -> RTCStats
toRTCStats :: forall o. IsRTCStats o => o -> RTCStats
toRTCStats = JSVal -> RTCStats
RTCStats (JSVal -> RTCStats) -> (o -> JSVal) -> o -> RTCStats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsRTCStats RTCStats
instance IsGObject RTCStats where
  typeGType :: RTCStats -> JSM GType
typeGType RTCStats
_ = JSM GType
gTypeRTCStats
  {-# INLINE typeGType #-}

noRTCStats :: Maybe RTCStats
noRTCStats :: Maybe RTCStats
noRTCStats = Maybe RTCStats
forall a. Maybe a
Nothing
{-# INLINE noRTCStats #-}

gTypeRTCStats :: JSM GType
gTypeRTCStats :: JSM GType
gTypeRTCStats = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCStats"

-- | Functions for this inteface are in "JSDOM.RTCStatsReport".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCStatsReport Mozilla RTCStatsReport documentation>
newtype RTCStatsReport = RTCStatsReport { RTCStatsReport -> JSVal
unRTCStatsReport :: JSVal }

instance PToJSVal RTCStatsReport where
  pToJSVal :: RTCStatsReport -> JSVal
pToJSVal = RTCStatsReport -> JSVal
unRTCStatsReport
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCStatsReport where
  pFromJSVal :: JSVal -> RTCStatsReport
pFromJSVal = JSVal -> RTCStatsReport
RTCStatsReport
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCStatsReport where
  toJSVal :: RTCStatsReport -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCStatsReport -> JSVal) -> RTCStatsReport -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCStatsReport -> JSVal
unRTCStatsReport
  {-# INLINE toJSVal #-}

instance FromJSVal RTCStatsReport where
  fromJSVal :: JSVal -> JSM (Maybe RTCStatsReport)
fromJSVal JSVal
v = (JSVal -> RTCStatsReport) -> Maybe JSVal -> Maybe RTCStatsReport
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCStatsReport
RTCStatsReport (Maybe JSVal -> Maybe RTCStatsReport)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCStatsReport)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCStatsReport
fromJSValUnchecked = RTCStatsReport -> JSM RTCStatsReport
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCStatsReport -> JSM RTCStatsReport)
-> (JSVal -> RTCStatsReport) -> JSVal -> JSM RTCStatsReport
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCStatsReport
RTCStatsReport
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCStatsReport where
  makeObject :: RTCStatsReport -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCStatsReport -> JSVal) -> RTCStatsReport -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCStatsReport -> JSVal
unRTCStatsReport

instance IsGObject RTCStatsReport where
  typeGType :: RTCStatsReport -> JSM GType
typeGType RTCStatsReport
_ = JSM GType
gTypeRTCStatsReport
  {-# INLINE typeGType #-}

noRTCStatsReport :: Maybe RTCStatsReport
noRTCStatsReport :: Maybe RTCStatsReport
noRTCStatsReport = Maybe RTCStatsReport
forall a. Maybe a
Nothing
{-# INLINE noRTCStatsReport #-}

gTypeRTCStatsReport :: JSM GType
gTypeRTCStatsReport :: JSM GType
gTypeRTCStatsReport = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCStatsReport"

-- | Functions for this inteface are in "JSDOM.RTCTrackEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCTrackEvent Mozilla RTCTrackEvent documentation>
newtype RTCTrackEvent = RTCTrackEvent { RTCTrackEvent -> JSVal
unRTCTrackEvent :: JSVal }

instance PToJSVal RTCTrackEvent where
  pToJSVal :: RTCTrackEvent -> JSVal
pToJSVal = RTCTrackEvent -> JSVal
unRTCTrackEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCTrackEvent where
  pFromJSVal :: JSVal -> RTCTrackEvent
pFromJSVal = JSVal -> RTCTrackEvent
RTCTrackEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCTrackEvent where
  toJSVal :: RTCTrackEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCTrackEvent -> JSVal) -> RTCTrackEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCTrackEvent -> JSVal
unRTCTrackEvent
  {-# INLINE toJSVal #-}

instance FromJSVal RTCTrackEvent where
  fromJSVal :: JSVal -> JSM (Maybe RTCTrackEvent)
fromJSVal JSVal
v = (JSVal -> RTCTrackEvent) -> Maybe JSVal -> Maybe RTCTrackEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCTrackEvent
RTCTrackEvent (Maybe JSVal -> Maybe RTCTrackEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCTrackEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCTrackEvent
fromJSValUnchecked = RTCTrackEvent -> JSM RTCTrackEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCTrackEvent -> JSM RTCTrackEvent)
-> (JSVal -> RTCTrackEvent) -> JSVal -> JSM RTCTrackEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCTrackEvent
RTCTrackEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCTrackEvent where
  makeObject :: RTCTrackEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCTrackEvent -> JSVal) -> RTCTrackEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCTrackEvent -> JSVal
unRTCTrackEvent

instance IsEvent RTCTrackEvent
instance IsGObject RTCTrackEvent where
  typeGType :: RTCTrackEvent -> JSM GType
typeGType RTCTrackEvent
_ = JSM GType
gTypeRTCTrackEvent
  {-# INLINE typeGType #-}

noRTCTrackEvent :: Maybe RTCTrackEvent
noRTCTrackEvent :: Maybe RTCTrackEvent
noRTCTrackEvent = Maybe RTCTrackEvent
forall a. Maybe a
Nothing
{-# INLINE noRTCTrackEvent #-}

gTypeRTCTrackEvent :: JSM GType
gTypeRTCTrackEvent :: JSM GType
gTypeRTCTrackEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCTrackEvent"

-- | Functions for this inteface are in "JSDOM.RTCTrackEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RTCTrackEventInit Mozilla RTCTrackEventInit documentation>
newtype RTCTrackEventInit = RTCTrackEventInit { RTCTrackEventInit -> JSVal
unRTCTrackEventInit :: JSVal }

instance PToJSVal RTCTrackEventInit where
  pToJSVal :: RTCTrackEventInit -> JSVal
pToJSVal = RTCTrackEventInit -> JSVal
unRTCTrackEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal RTCTrackEventInit where
  pFromJSVal :: JSVal -> RTCTrackEventInit
pFromJSVal = JSVal -> RTCTrackEventInit
RTCTrackEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal RTCTrackEventInit where
  toJSVal :: RTCTrackEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RTCTrackEventInit -> JSVal) -> RTCTrackEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCTrackEventInit -> JSVal
unRTCTrackEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal RTCTrackEventInit where
  fromJSVal :: JSVal -> JSM (Maybe RTCTrackEventInit)
fromJSVal JSVal
v = (JSVal -> RTCTrackEventInit)
-> Maybe JSVal -> Maybe RTCTrackEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RTCTrackEventInit
RTCTrackEventInit (Maybe JSVal -> Maybe RTCTrackEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe RTCTrackEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RTCTrackEventInit
fromJSValUnchecked = RTCTrackEventInit -> JSM RTCTrackEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCTrackEventInit -> JSM RTCTrackEventInit)
-> (JSVal -> RTCTrackEventInit) -> JSVal -> JSM RTCTrackEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RTCTrackEventInit
RTCTrackEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RTCTrackEventInit where
  makeObject :: RTCTrackEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RTCTrackEventInit -> JSVal) -> RTCTrackEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTCTrackEventInit -> JSVal
unRTCTrackEventInit

instance IsEventInit RTCTrackEventInit
instance IsGObject RTCTrackEventInit where
  typeGType :: RTCTrackEventInit -> JSM GType
typeGType RTCTrackEventInit
_ = JSM GType
gTypeRTCTrackEventInit
  {-# INLINE typeGType #-}

noRTCTrackEventInit :: Maybe RTCTrackEventInit
noRTCTrackEventInit :: Maybe RTCTrackEventInit
noRTCTrackEventInit = Maybe RTCTrackEventInit
forall a. Maybe a
Nothing
{-# INLINE noRTCTrackEventInit #-}

gTypeRTCTrackEventInit :: JSM GType
gTypeRTCTrackEventInit :: JSM GType
gTypeRTCTrackEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RTCTrackEventInit"

-- | Functions for this inteface are in "JSDOM.RadioNodeList".
-- Base interface functions are in:
--
--     * "JSDOM.NodeList"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RadioNodeList Mozilla RadioNodeList documentation>
newtype RadioNodeList = RadioNodeList { RadioNodeList -> JSVal
unRadioNodeList :: JSVal }

instance PToJSVal RadioNodeList where
  pToJSVal :: RadioNodeList -> JSVal
pToJSVal = RadioNodeList -> JSVal
unRadioNodeList
  {-# INLINE pToJSVal #-}

instance PFromJSVal RadioNodeList where
  pFromJSVal :: JSVal -> RadioNodeList
pFromJSVal = JSVal -> RadioNodeList
RadioNodeList
  {-# INLINE pFromJSVal #-}

instance ToJSVal RadioNodeList where
  toJSVal :: RadioNodeList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RadioNodeList -> JSVal) -> RadioNodeList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RadioNodeList -> JSVal
unRadioNodeList
  {-# INLINE toJSVal #-}

instance FromJSVal RadioNodeList where
  fromJSVal :: JSVal -> JSM (Maybe RadioNodeList)
fromJSVal JSVal
v = (JSVal -> RadioNodeList) -> Maybe JSVal -> Maybe RadioNodeList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RadioNodeList
RadioNodeList (Maybe JSVal -> Maybe RadioNodeList)
-> JSM (Maybe JSVal) -> JSM (Maybe RadioNodeList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RadioNodeList
fromJSValUnchecked = RadioNodeList -> JSM RadioNodeList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RadioNodeList -> JSM RadioNodeList)
-> (JSVal -> RadioNodeList) -> JSVal -> JSM RadioNodeList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RadioNodeList
RadioNodeList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RadioNodeList where
  makeObject :: RadioNodeList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RadioNodeList -> JSVal) -> RadioNodeList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RadioNodeList -> JSVal
unRadioNodeList

instance IsNodeList RadioNodeList
instance IsGObject RadioNodeList where
  typeGType :: RadioNodeList -> JSM GType
typeGType RadioNodeList
_ = JSM GType
gTypeRadioNodeList
  {-# INLINE typeGType #-}

noRadioNodeList :: Maybe RadioNodeList
noRadioNodeList :: Maybe RadioNodeList
noRadioNodeList = Maybe RadioNodeList
forall a. Maybe a
Nothing
{-# INLINE noRadioNodeList #-}

gTypeRadioNodeList :: JSM GType
gTypeRadioNodeList :: JSM GType
gTypeRadioNodeList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RadioNodeList"

-- | Functions for this inteface are in "JSDOM.Range".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Range Mozilla Range documentation>
newtype Range = Range { Range -> JSVal
unRange :: JSVal }

instance PToJSVal Range where
  pToJSVal :: Range -> JSVal
pToJSVal = Range -> JSVal
unRange
  {-# INLINE pToJSVal #-}

instance PFromJSVal Range where
  pFromJSVal :: JSVal -> Range
pFromJSVal = JSVal -> Range
Range
  {-# INLINE pFromJSVal #-}

instance ToJSVal Range where
  toJSVal :: Range -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Range -> JSVal) -> Range -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Range -> JSVal
unRange
  {-# INLINE toJSVal #-}

instance FromJSVal Range where
  fromJSVal :: JSVal -> JSM (Maybe Range)
fromJSVal JSVal
v = (JSVal -> Range) -> Maybe JSVal -> Maybe Range
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Range
Range (Maybe JSVal -> Maybe Range)
-> JSM (Maybe JSVal) -> JSM (Maybe Range)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Range
fromJSValUnchecked = Range -> JSM Range
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Range -> JSM Range) -> (JSVal -> Range) -> JSVal -> JSM Range
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Range
Range
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Range where
  makeObject :: Range -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Range -> JSVal) -> Range -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Range -> JSVal
unRange

instance IsGObject Range where
  typeGType :: Range -> JSM GType
typeGType Range
_ = JSM GType
gTypeRange
  {-# INLINE typeGType #-}

noRange :: Maybe Range
noRange :: Maybe Range
noRange = Maybe Range
forall a. Maybe a
Nothing
{-# INLINE noRange #-}

gTypeRange :: JSM GType
gTypeRange :: JSM GType
gTypeRange = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Range"

-- | Functions for this inteface are in "JSDOM.ReadableByteStreamController".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ReadableByteStreamController Mozilla ReadableByteStreamController documentation>
newtype ReadableByteStreamController = ReadableByteStreamController { ReadableByteStreamController -> JSVal
unReadableByteStreamController :: JSVal }

instance PToJSVal ReadableByteStreamController where
  pToJSVal :: ReadableByteStreamController -> JSVal
pToJSVal = ReadableByteStreamController -> JSVal
unReadableByteStreamController
  {-# INLINE pToJSVal #-}

instance PFromJSVal ReadableByteStreamController where
  pFromJSVal :: JSVal -> ReadableByteStreamController
pFromJSVal = JSVal -> ReadableByteStreamController
ReadableByteStreamController
  {-# INLINE pFromJSVal #-}

instance ToJSVal ReadableByteStreamController where
  toJSVal :: ReadableByteStreamController -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ReadableByteStreamController -> JSVal)
-> ReadableByteStreamController
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableByteStreamController -> JSVal
unReadableByteStreamController
  {-# INLINE toJSVal #-}

instance FromJSVal ReadableByteStreamController where
  fromJSVal :: JSVal -> JSM (Maybe ReadableByteStreamController)
fromJSVal JSVal
v = (JSVal -> ReadableByteStreamController)
-> Maybe JSVal -> Maybe ReadableByteStreamController
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ReadableByteStreamController
ReadableByteStreamController (Maybe JSVal -> Maybe ReadableByteStreamController)
-> JSM (Maybe JSVal) -> JSM (Maybe ReadableByteStreamController)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ReadableByteStreamController
fromJSValUnchecked = ReadableByteStreamController -> JSM ReadableByteStreamController
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ReadableByteStreamController -> JSM ReadableByteStreamController)
-> (JSVal -> ReadableByteStreamController)
-> JSVal
-> JSM ReadableByteStreamController
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ReadableByteStreamController
ReadableByteStreamController
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ReadableByteStreamController where
  makeObject :: ReadableByteStreamController -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ReadableByteStreamController -> JSVal)
-> ReadableByteStreamController
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableByteStreamController -> JSVal
unReadableByteStreamController

instance IsGObject ReadableByteStreamController where
  typeGType :: ReadableByteStreamController -> JSM GType
typeGType ReadableByteStreamController
_ = JSM GType
gTypeReadableByteStreamController
  {-# INLINE typeGType #-}

noReadableByteStreamController :: Maybe ReadableByteStreamController
noReadableByteStreamController :: Maybe ReadableByteStreamController
noReadableByteStreamController = Maybe ReadableByteStreamController
forall a. Maybe a
Nothing
{-# INLINE noReadableByteStreamController #-}

gTypeReadableByteStreamController :: JSM GType
gTypeReadableByteStreamController :: JSM GType
gTypeReadableByteStreamController = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ReadableByteStreamController"

-- | Functions for this inteface are in "JSDOM.ReadableStream".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ReadableStream Mozilla ReadableStream documentation>
newtype ReadableStream = ReadableStream { ReadableStream -> JSVal
unReadableStream :: JSVal }

instance PToJSVal ReadableStream where
  pToJSVal :: ReadableStream -> JSVal
pToJSVal = ReadableStream -> JSVal
unReadableStream
  {-# INLINE pToJSVal #-}

instance PFromJSVal ReadableStream where
  pFromJSVal :: JSVal -> ReadableStream
pFromJSVal = JSVal -> ReadableStream
ReadableStream
  {-# INLINE pFromJSVal #-}

instance ToJSVal ReadableStream where
  toJSVal :: ReadableStream -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ReadableStream -> JSVal) -> ReadableStream -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStream -> JSVal
unReadableStream
  {-# INLINE toJSVal #-}

instance FromJSVal ReadableStream where
  fromJSVal :: JSVal -> JSM (Maybe ReadableStream)
fromJSVal JSVal
v = (JSVal -> ReadableStream) -> Maybe JSVal -> Maybe ReadableStream
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ReadableStream
ReadableStream (Maybe JSVal -> Maybe ReadableStream)
-> JSM (Maybe JSVal) -> JSM (Maybe ReadableStream)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ReadableStream
fromJSValUnchecked = ReadableStream -> JSM ReadableStream
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ReadableStream -> JSM ReadableStream)
-> (JSVal -> ReadableStream) -> JSVal -> JSM ReadableStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ReadableStream
ReadableStream
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ReadableStream where
  makeObject :: ReadableStream -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ReadableStream -> JSVal) -> ReadableStream -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStream -> JSVal
unReadableStream

instance IsGObject ReadableStream where
  typeGType :: ReadableStream -> JSM GType
typeGType ReadableStream
_ = JSM GType
gTypeReadableStream
  {-# INLINE typeGType #-}

noReadableStream :: Maybe ReadableStream
noReadableStream :: Maybe ReadableStream
noReadableStream = Maybe ReadableStream
forall a. Maybe a
Nothing
{-# INLINE noReadableStream #-}

gTypeReadableStream :: JSM GType
gTypeReadableStream :: JSM GType
gTypeReadableStream = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ReadableStream"

-- | Functions for this inteface are in "JSDOM.ReadableStreamBYOBReader".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ReadableStreamBYOBReader Mozilla ReadableStreamBYOBReader documentation>
newtype ReadableStreamBYOBReader = ReadableStreamBYOBReader { ReadableStreamBYOBReader -> JSVal
unReadableStreamBYOBReader :: JSVal }

instance PToJSVal ReadableStreamBYOBReader where
  pToJSVal :: ReadableStreamBYOBReader -> JSVal
pToJSVal = ReadableStreamBYOBReader -> JSVal
unReadableStreamBYOBReader
  {-# INLINE pToJSVal #-}

instance PFromJSVal ReadableStreamBYOBReader where
  pFromJSVal :: JSVal -> ReadableStreamBYOBReader
pFromJSVal = JSVal -> ReadableStreamBYOBReader
ReadableStreamBYOBReader
  {-# INLINE pFromJSVal #-}

instance ToJSVal ReadableStreamBYOBReader where
  toJSVal :: ReadableStreamBYOBReader -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ReadableStreamBYOBReader -> JSVal)
-> ReadableStreamBYOBReader
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStreamBYOBReader -> JSVal
unReadableStreamBYOBReader
  {-# INLINE toJSVal #-}

instance FromJSVal ReadableStreamBYOBReader where
  fromJSVal :: JSVal -> JSM (Maybe ReadableStreamBYOBReader)
fromJSVal JSVal
v = (JSVal -> ReadableStreamBYOBReader)
-> Maybe JSVal -> Maybe ReadableStreamBYOBReader
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ReadableStreamBYOBReader
ReadableStreamBYOBReader (Maybe JSVal -> Maybe ReadableStreamBYOBReader)
-> JSM (Maybe JSVal) -> JSM (Maybe ReadableStreamBYOBReader)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ReadableStreamBYOBReader
fromJSValUnchecked = ReadableStreamBYOBReader -> JSM ReadableStreamBYOBReader
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ReadableStreamBYOBReader -> JSM ReadableStreamBYOBReader)
-> (JSVal -> ReadableStreamBYOBReader)
-> JSVal
-> JSM ReadableStreamBYOBReader
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ReadableStreamBYOBReader
ReadableStreamBYOBReader
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ReadableStreamBYOBReader where
  makeObject :: ReadableStreamBYOBReader -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ReadableStreamBYOBReader -> JSVal)
-> ReadableStreamBYOBReader
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStreamBYOBReader -> JSVal
unReadableStreamBYOBReader

instance IsGObject ReadableStreamBYOBReader where
  typeGType :: ReadableStreamBYOBReader -> JSM GType
typeGType ReadableStreamBYOBReader
_ = JSM GType
gTypeReadableStreamBYOBReader
  {-# INLINE typeGType #-}

noReadableStreamBYOBReader :: Maybe ReadableStreamBYOBReader
noReadableStreamBYOBReader :: Maybe ReadableStreamBYOBReader
noReadableStreamBYOBReader = Maybe ReadableStreamBYOBReader
forall a. Maybe a
Nothing
{-# INLINE noReadableStreamBYOBReader #-}

gTypeReadableStreamBYOBReader :: JSM GType
gTypeReadableStreamBYOBReader :: JSM GType
gTypeReadableStreamBYOBReader = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ReadableStreamBYOBReader"

-- | Functions for this inteface are in "JSDOM.ReadableStreamBYOBRequest".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ReadableStreamBYOBRequest Mozilla ReadableStreamBYOBRequest documentation>
newtype ReadableStreamBYOBRequest = ReadableStreamBYOBRequest { ReadableStreamBYOBRequest -> JSVal
unReadableStreamBYOBRequest :: JSVal }

instance PToJSVal ReadableStreamBYOBRequest where
  pToJSVal :: ReadableStreamBYOBRequest -> JSVal
pToJSVal = ReadableStreamBYOBRequest -> JSVal
unReadableStreamBYOBRequest
  {-# INLINE pToJSVal #-}

instance PFromJSVal ReadableStreamBYOBRequest where
  pFromJSVal :: JSVal -> ReadableStreamBYOBRequest
pFromJSVal = JSVal -> ReadableStreamBYOBRequest
ReadableStreamBYOBRequest
  {-# INLINE pFromJSVal #-}

instance ToJSVal ReadableStreamBYOBRequest where
  toJSVal :: ReadableStreamBYOBRequest -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ReadableStreamBYOBRequest -> JSVal)
-> ReadableStreamBYOBRequest
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStreamBYOBRequest -> JSVal
unReadableStreamBYOBRequest
  {-# INLINE toJSVal #-}

instance FromJSVal ReadableStreamBYOBRequest where
  fromJSVal :: JSVal -> JSM (Maybe ReadableStreamBYOBRequest)
fromJSVal JSVal
v = (JSVal -> ReadableStreamBYOBRequest)
-> Maybe JSVal -> Maybe ReadableStreamBYOBRequest
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ReadableStreamBYOBRequest
ReadableStreamBYOBRequest (Maybe JSVal -> Maybe ReadableStreamBYOBRequest)
-> JSM (Maybe JSVal) -> JSM (Maybe ReadableStreamBYOBRequest)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ReadableStreamBYOBRequest
fromJSValUnchecked = ReadableStreamBYOBRequest -> JSM ReadableStreamBYOBRequest
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ReadableStreamBYOBRequest -> JSM ReadableStreamBYOBRequest)
-> (JSVal -> ReadableStreamBYOBRequest)
-> JSVal
-> JSM ReadableStreamBYOBRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ReadableStreamBYOBRequest
ReadableStreamBYOBRequest
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ReadableStreamBYOBRequest where
  makeObject :: ReadableStreamBYOBRequest -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ReadableStreamBYOBRequest -> JSVal)
-> ReadableStreamBYOBRequest
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStreamBYOBRequest -> JSVal
unReadableStreamBYOBRequest

instance IsGObject ReadableStreamBYOBRequest where
  typeGType :: ReadableStreamBYOBRequest -> JSM GType
typeGType ReadableStreamBYOBRequest
_ = JSM GType
gTypeReadableStreamBYOBRequest
  {-# INLINE typeGType #-}

noReadableStreamBYOBRequest :: Maybe ReadableStreamBYOBRequest
noReadableStreamBYOBRequest :: Maybe ReadableStreamBYOBRequest
noReadableStreamBYOBRequest = Maybe ReadableStreamBYOBRequest
forall a. Maybe a
Nothing
{-# INLINE noReadableStreamBYOBRequest #-}

gTypeReadableStreamBYOBRequest :: JSM GType
gTypeReadableStreamBYOBRequest :: JSM GType
gTypeReadableStreamBYOBRequest = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ReadableStreamBYOBRequest"

-- | Functions for this inteface are in "JSDOM.ReadableStreamDefaultController".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ReadableStreamDefaultController Mozilla ReadableStreamDefaultController documentation>
newtype ReadableStreamDefaultController = ReadableStreamDefaultController { ReadableStreamDefaultController -> JSVal
unReadableStreamDefaultController :: JSVal }

instance PToJSVal ReadableStreamDefaultController where
  pToJSVal :: ReadableStreamDefaultController -> JSVal
pToJSVal = ReadableStreamDefaultController -> JSVal
unReadableStreamDefaultController
  {-# INLINE pToJSVal #-}

instance PFromJSVal ReadableStreamDefaultController where
  pFromJSVal :: JSVal -> ReadableStreamDefaultController
pFromJSVal = JSVal -> ReadableStreamDefaultController
ReadableStreamDefaultController
  {-# INLINE pFromJSVal #-}

instance ToJSVal ReadableStreamDefaultController where
  toJSVal :: ReadableStreamDefaultController -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ReadableStreamDefaultController -> JSVal)
-> ReadableStreamDefaultController
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStreamDefaultController -> JSVal
unReadableStreamDefaultController
  {-# INLINE toJSVal #-}

instance FromJSVal ReadableStreamDefaultController where
  fromJSVal :: JSVal -> JSM (Maybe ReadableStreamDefaultController)
fromJSVal JSVal
v = (JSVal -> ReadableStreamDefaultController)
-> Maybe JSVal -> Maybe ReadableStreamDefaultController
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ReadableStreamDefaultController
ReadableStreamDefaultController (Maybe JSVal -> Maybe ReadableStreamDefaultController)
-> JSM (Maybe JSVal) -> JSM (Maybe ReadableStreamDefaultController)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ReadableStreamDefaultController
fromJSValUnchecked = ReadableStreamDefaultController
-> JSM ReadableStreamDefaultController
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ReadableStreamDefaultController
 -> JSM ReadableStreamDefaultController)
-> (JSVal -> ReadableStreamDefaultController)
-> JSVal
-> JSM ReadableStreamDefaultController
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ReadableStreamDefaultController
ReadableStreamDefaultController
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ReadableStreamDefaultController where
  makeObject :: ReadableStreamDefaultController -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ReadableStreamDefaultController -> JSVal)
-> ReadableStreamDefaultController
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStreamDefaultController -> JSVal
unReadableStreamDefaultController

instance IsGObject ReadableStreamDefaultController where
  typeGType :: ReadableStreamDefaultController -> JSM GType
typeGType ReadableStreamDefaultController
_ = JSM GType
gTypeReadableStreamDefaultController
  {-# INLINE typeGType #-}

noReadableStreamDefaultController :: Maybe ReadableStreamDefaultController
noReadableStreamDefaultController :: Maybe ReadableStreamDefaultController
noReadableStreamDefaultController = Maybe ReadableStreamDefaultController
forall a. Maybe a
Nothing
{-# INLINE noReadableStreamDefaultController #-}

gTypeReadableStreamDefaultController :: JSM GType
gTypeReadableStreamDefaultController :: JSM GType
gTypeReadableStreamDefaultController = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ReadableStreamDefaultController"

-- | Functions for this inteface are in "JSDOM.ReadableStreamDefaultReader".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ReadableStreamDefaultReader Mozilla ReadableStreamDefaultReader documentation>
newtype ReadableStreamDefaultReader = ReadableStreamDefaultReader { ReadableStreamDefaultReader -> JSVal
unReadableStreamDefaultReader :: JSVal }

instance PToJSVal ReadableStreamDefaultReader where
  pToJSVal :: ReadableStreamDefaultReader -> JSVal
pToJSVal = ReadableStreamDefaultReader -> JSVal
unReadableStreamDefaultReader
  {-# INLINE pToJSVal #-}

instance PFromJSVal ReadableStreamDefaultReader where
  pFromJSVal :: JSVal -> ReadableStreamDefaultReader
pFromJSVal = JSVal -> ReadableStreamDefaultReader
ReadableStreamDefaultReader
  {-# INLINE pFromJSVal #-}

instance ToJSVal ReadableStreamDefaultReader where
  toJSVal :: ReadableStreamDefaultReader -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ReadableStreamDefaultReader -> JSVal)
-> ReadableStreamDefaultReader
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStreamDefaultReader -> JSVal
unReadableStreamDefaultReader
  {-# INLINE toJSVal #-}

instance FromJSVal ReadableStreamDefaultReader where
  fromJSVal :: JSVal -> JSM (Maybe ReadableStreamDefaultReader)
fromJSVal JSVal
v = (JSVal -> ReadableStreamDefaultReader)
-> Maybe JSVal -> Maybe ReadableStreamDefaultReader
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ReadableStreamDefaultReader
ReadableStreamDefaultReader (Maybe JSVal -> Maybe ReadableStreamDefaultReader)
-> JSM (Maybe JSVal) -> JSM (Maybe ReadableStreamDefaultReader)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ReadableStreamDefaultReader
fromJSValUnchecked = ReadableStreamDefaultReader -> JSM ReadableStreamDefaultReader
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ReadableStreamDefaultReader -> JSM ReadableStreamDefaultReader)
-> (JSVal -> ReadableStreamDefaultReader)
-> JSVal
-> JSM ReadableStreamDefaultReader
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ReadableStreamDefaultReader
ReadableStreamDefaultReader
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ReadableStreamDefaultReader where
  makeObject :: ReadableStreamDefaultReader -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ReadableStreamDefaultReader -> JSVal)
-> ReadableStreamDefaultReader
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStreamDefaultReader -> JSVal
unReadableStreamDefaultReader

instance IsGObject ReadableStreamDefaultReader where
  typeGType :: ReadableStreamDefaultReader -> JSM GType
typeGType ReadableStreamDefaultReader
_ = JSM GType
gTypeReadableStreamDefaultReader
  {-# INLINE typeGType #-}

noReadableStreamDefaultReader :: Maybe ReadableStreamDefaultReader
noReadableStreamDefaultReader :: Maybe ReadableStreamDefaultReader
noReadableStreamDefaultReader = Maybe ReadableStreamDefaultReader
forall a. Maybe a
Nothing
{-# INLINE noReadableStreamDefaultReader #-}

gTypeReadableStreamDefaultReader :: JSM GType
gTypeReadableStreamDefaultReader :: JSM GType
gTypeReadableStreamDefaultReader = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ReadableStreamDefaultReader"

-- | Functions for this inteface are in "JSDOM.ReadableStreamSource".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ReadableStreamSource Mozilla ReadableStreamSource documentation>
newtype ReadableStreamSource = ReadableStreamSource { ReadableStreamSource -> JSVal
unReadableStreamSource :: JSVal }

instance PToJSVal ReadableStreamSource where
  pToJSVal :: ReadableStreamSource -> JSVal
pToJSVal = ReadableStreamSource -> JSVal
unReadableStreamSource
  {-# INLINE pToJSVal #-}

instance PFromJSVal ReadableStreamSource where
  pFromJSVal :: JSVal -> ReadableStreamSource
pFromJSVal = JSVal -> ReadableStreamSource
ReadableStreamSource
  {-# INLINE pFromJSVal #-}

instance ToJSVal ReadableStreamSource where
  toJSVal :: ReadableStreamSource -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ReadableStreamSource -> JSVal)
-> ReadableStreamSource
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStreamSource -> JSVal
unReadableStreamSource
  {-# INLINE toJSVal #-}

instance FromJSVal ReadableStreamSource where
  fromJSVal :: JSVal -> JSM (Maybe ReadableStreamSource)
fromJSVal JSVal
v = (JSVal -> ReadableStreamSource)
-> Maybe JSVal -> Maybe ReadableStreamSource
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ReadableStreamSource
ReadableStreamSource (Maybe JSVal -> Maybe ReadableStreamSource)
-> JSM (Maybe JSVal) -> JSM (Maybe ReadableStreamSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ReadableStreamSource
fromJSValUnchecked = ReadableStreamSource -> JSM ReadableStreamSource
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ReadableStreamSource -> JSM ReadableStreamSource)
-> (JSVal -> ReadableStreamSource)
-> JSVal
-> JSM ReadableStreamSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ReadableStreamSource
ReadableStreamSource
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ReadableStreamSource where
  makeObject :: ReadableStreamSource -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ReadableStreamSource -> JSVal)
-> ReadableStreamSource
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadableStreamSource -> JSVal
unReadableStreamSource

instance IsGObject ReadableStreamSource where
  typeGType :: ReadableStreamSource -> JSM GType
typeGType ReadableStreamSource
_ = JSM GType
gTypeReadableStreamSource
  {-# INLINE typeGType #-}

noReadableStreamSource :: Maybe ReadableStreamSource
noReadableStreamSource :: Maybe ReadableStreamSource
noReadableStreamSource = Maybe ReadableStreamSource
forall a. Maybe a
Nothing
{-# INLINE noReadableStreamSource #-}

gTypeReadableStreamSource :: JSM GType
gTypeReadableStreamSource :: JSM GType
gTypeReadableStreamSource = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ReadableStreamSource"

-- | Functions for this inteface are in "JSDOM.Rect".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Rect Mozilla Rect documentation>
newtype Rect = Rect { Rect -> JSVal
unRect :: JSVal }

instance PToJSVal Rect where
  pToJSVal :: Rect -> JSVal
pToJSVal = Rect -> JSVal
unRect
  {-# INLINE pToJSVal #-}

instance PFromJSVal Rect where
  pFromJSVal :: JSVal -> Rect
pFromJSVal = JSVal -> Rect
Rect
  {-# INLINE pFromJSVal #-}

instance ToJSVal Rect where
  toJSVal :: Rect -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Rect -> JSVal) -> Rect -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rect -> JSVal
unRect
  {-# INLINE toJSVal #-}

instance FromJSVal Rect where
  fromJSVal :: JSVal -> JSM (Maybe Rect)
fromJSVal JSVal
v = (JSVal -> Rect) -> Maybe JSVal -> Maybe Rect
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Rect
Rect (Maybe JSVal -> Maybe Rect)
-> JSM (Maybe JSVal) -> JSM (Maybe Rect)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Rect
fromJSValUnchecked = Rect -> JSM Rect
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Rect -> JSM Rect) -> (JSVal -> Rect) -> JSVal -> JSM Rect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Rect
Rect
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Rect where
  makeObject :: Rect -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Rect -> JSVal) -> Rect -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rect -> JSVal
unRect

instance IsGObject Rect where
  typeGType :: Rect -> JSM GType
typeGType Rect
_ = JSM GType
gTypeRect
  {-# INLINE typeGType #-}

noRect :: Maybe Rect
noRect :: Maybe Rect
noRect = Maybe Rect
forall a. Maybe a
Nothing
{-# INLINE noRect #-}

gTypeRect :: JSM GType
gTypeRect :: JSM GType
gTypeRect = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Rect"

-- | Functions for this inteface are in "JSDOM.Request".
-- Base interface functions are in:
--
--     * "JSDOM.Body"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Request Mozilla Request documentation>
newtype Request = Request { Request -> JSVal
unRequest :: JSVal }

instance PToJSVal Request where
  pToJSVal :: Request -> JSVal
pToJSVal = Request -> JSVal
unRequest
  {-# INLINE pToJSVal #-}

instance PFromJSVal Request where
  pFromJSVal :: JSVal -> Request
pFromJSVal = JSVal -> Request
Request
  {-# INLINE pFromJSVal #-}

instance ToJSVal Request where
  toJSVal :: Request -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Request -> JSVal) -> Request -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Request -> JSVal
unRequest
  {-# INLINE toJSVal #-}

instance FromJSVal Request where
  fromJSVal :: JSVal -> JSM (Maybe Request)
fromJSVal JSVal
v = (JSVal -> Request) -> Maybe JSVal -> Maybe Request
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Request
Request (Maybe JSVal -> Maybe Request)
-> JSM (Maybe JSVal) -> JSM (Maybe Request)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Request
fromJSValUnchecked = Request -> JSM Request
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Request -> JSM Request)
-> (JSVal -> Request) -> JSVal -> JSM Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Request
Request
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Request where
  makeObject :: Request -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Request -> JSVal) -> Request -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Request -> JSVal
unRequest

instance IsBody Request
instance IsGObject Request where
  typeGType :: Request -> JSM GType
typeGType Request
_ = JSM GType
gTypeRequest
  {-# INLINE typeGType #-}

noRequest :: Maybe Request
noRequest :: Maybe Request
noRequest = Maybe Request
forall a. Maybe a
Nothing
{-# INLINE noRequest #-}

gTypeRequest :: JSM GType
gTypeRequest :: JSM GType
gTypeRequest = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Request"

-- | Functions for this inteface are in "JSDOM.RequestInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RequestInit Mozilla RequestInit documentation>
newtype RequestInit = RequestInit { RequestInit -> JSVal
unRequestInit :: JSVal }

instance PToJSVal RequestInit where
  pToJSVal :: RequestInit -> JSVal
pToJSVal = RequestInit -> JSVal
unRequestInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal RequestInit where
  pFromJSVal :: JSVal -> RequestInit
pFromJSVal = JSVal -> RequestInit
RequestInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal RequestInit where
  toJSVal :: RequestInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RequestInit -> JSVal) -> RequestInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RequestInit -> JSVal
unRequestInit
  {-# INLINE toJSVal #-}

instance FromJSVal RequestInit where
  fromJSVal :: JSVal -> JSM (Maybe RequestInit)
fromJSVal JSVal
v = (JSVal -> RequestInit) -> Maybe JSVal -> Maybe RequestInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RequestInit
RequestInit (Maybe JSVal -> Maybe RequestInit)
-> JSM (Maybe JSVal) -> JSM (Maybe RequestInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RequestInit
fromJSValUnchecked = RequestInit -> JSM RequestInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestInit -> JSM RequestInit)
-> (JSVal -> RequestInit) -> JSVal -> JSM RequestInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RequestInit
RequestInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RequestInit where
  makeObject :: RequestInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RequestInit -> JSVal) -> RequestInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RequestInit -> JSVal
unRequestInit

instance IsGObject RequestInit where
  typeGType :: RequestInit -> JSM GType
typeGType RequestInit
_ = JSM GType
gTypeRequestInit
  {-# INLINE typeGType #-}

noRequestInit :: Maybe RequestInit
noRequestInit :: Maybe RequestInit
noRequestInit = Maybe RequestInit
forall a. Maybe a
Nothing
{-# INLINE noRequestInit #-}

gTypeRequestInit :: JSM GType
gTypeRequestInit :: JSM GType
gTypeRequestInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RequestInit"

-- | Functions for this inteface are in "JSDOM.Response".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Response Mozilla Response documentation>
newtype Response = Response { Response -> JSVal
unResponse :: JSVal }

instance PToJSVal Response where
  pToJSVal :: Response -> JSVal
pToJSVal = Response -> JSVal
unResponse
  {-# INLINE pToJSVal #-}

instance PFromJSVal Response where
  pFromJSVal :: JSVal -> Response
pFromJSVal = JSVal -> Response
Response
  {-# INLINE pFromJSVal #-}

instance ToJSVal Response where
  toJSVal :: Response -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Response -> JSVal) -> Response -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Response -> JSVal
unResponse
  {-# INLINE toJSVal #-}

instance FromJSVal Response where
  fromJSVal :: JSVal -> JSM (Maybe Response)
fromJSVal JSVal
v = (JSVal -> Response) -> Maybe JSVal -> Maybe Response
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Response
Response (Maybe JSVal -> Maybe Response)
-> JSM (Maybe JSVal) -> JSM (Maybe Response)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Response
fromJSValUnchecked = Response -> JSM Response
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Response -> JSM Response)
-> (JSVal -> Response) -> JSVal -> JSM Response
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Response
Response
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Response where
  makeObject :: Response -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Response -> JSVal) -> Response -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Response -> JSVal
unResponse

instance IsGObject Response where
  typeGType :: Response -> JSM GType
typeGType Response
_ = JSM GType
gTypeResponse
  {-# INLINE typeGType #-}

noResponse :: Maybe Response
noResponse :: Maybe Response
noResponse = Maybe Response
forall a. Maybe a
Nothing
{-# INLINE noResponse #-}

gTypeResponse :: JSM GType
gTypeResponse :: JSM GType
gTypeResponse = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Response"

-- | Functions for this inteface are in "JSDOM.RotationRate".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RotationRate Mozilla RotationRate documentation>
newtype RotationRate = RotationRate { RotationRate -> JSVal
unRotationRate :: JSVal }

instance PToJSVal RotationRate where
  pToJSVal :: RotationRate -> JSVal
pToJSVal = RotationRate -> JSVal
unRotationRate
  {-# INLINE pToJSVal #-}

instance PFromJSVal RotationRate where
  pFromJSVal :: JSVal -> RotationRate
pFromJSVal = JSVal -> RotationRate
RotationRate
  {-# INLINE pFromJSVal #-}

instance ToJSVal RotationRate where
  toJSVal :: RotationRate -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RotationRate -> JSVal) -> RotationRate -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RotationRate -> JSVal
unRotationRate
  {-# INLINE toJSVal #-}

instance FromJSVal RotationRate where
  fromJSVal :: JSVal -> JSM (Maybe RotationRate)
fromJSVal JSVal
v = (JSVal -> RotationRate) -> Maybe JSVal -> Maybe RotationRate
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RotationRate
RotationRate (Maybe JSVal -> Maybe RotationRate)
-> JSM (Maybe JSVal) -> JSM (Maybe RotationRate)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RotationRate
fromJSValUnchecked = RotationRate -> JSM RotationRate
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RotationRate -> JSM RotationRate)
-> (JSVal -> RotationRate) -> JSVal -> JSM RotationRate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RotationRate
RotationRate
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RotationRate where
  makeObject :: RotationRate -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RotationRate -> JSVal) -> RotationRate -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RotationRate -> JSVal
unRotationRate

instance IsGObject RotationRate where
  typeGType :: RotationRate -> JSM GType
typeGType RotationRate
_ = JSM GType
gTypeRotationRate
  {-# INLINE typeGType #-}

noRotationRate :: Maybe RotationRate
noRotationRate :: Maybe RotationRate
noRotationRate = Maybe RotationRate
forall a. Maybe a
Nothing
{-# INLINE noRotationRate #-}

gTypeRotationRate :: JSM GType
gTypeRotationRate :: JSM GType
gTypeRotationRate = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RotationRate"

-- | Functions for this inteface are in "JSDOM.RsaHashedImportParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RsaHashedImportParams Mozilla RsaHashedImportParams documentation>
newtype RsaHashedImportParams = RsaHashedImportParams { RsaHashedImportParams -> JSVal
unRsaHashedImportParams :: JSVal }

instance PToJSVal RsaHashedImportParams where
  pToJSVal :: RsaHashedImportParams -> JSVal
pToJSVal = RsaHashedImportParams -> JSVal
unRsaHashedImportParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal RsaHashedImportParams where
  pFromJSVal :: JSVal -> RsaHashedImportParams
pFromJSVal = JSVal -> RsaHashedImportParams
RsaHashedImportParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal RsaHashedImportParams where
  toJSVal :: RsaHashedImportParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RsaHashedImportParams -> JSVal)
-> RsaHashedImportParams
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RsaHashedImportParams -> JSVal
unRsaHashedImportParams
  {-# INLINE toJSVal #-}

instance FromJSVal RsaHashedImportParams where
  fromJSVal :: JSVal -> JSM (Maybe RsaHashedImportParams)
fromJSVal JSVal
v = (JSVal -> RsaHashedImportParams)
-> Maybe JSVal -> Maybe RsaHashedImportParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RsaHashedImportParams
RsaHashedImportParams (Maybe JSVal -> Maybe RsaHashedImportParams)
-> JSM (Maybe JSVal) -> JSM (Maybe RsaHashedImportParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RsaHashedImportParams
fromJSValUnchecked = RsaHashedImportParams -> JSM RsaHashedImportParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RsaHashedImportParams -> JSM RsaHashedImportParams)
-> (JSVal -> RsaHashedImportParams)
-> JSVal
-> JSM RsaHashedImportParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RsaHashedImportParams
RsaHashedImportParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RsaHashedImportParams where
  makeObject :: RsaHashedImportParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RsaHashedImportParams -> JSVal)
-> RsaHashedImportParams
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RsaHashedImportParams -> JSVal
unRsaHashedImportParams

instance IsCryptoAlgorithmParameters RsaHashedImportParams
instance IsGObject RsaHashedImportParams where
  typeGType :: RsaHashedImportParams -> JSM GType
typeGType RsaHashedImportParams
_ = JSM GType
gTypeRsaHashedImportParams
  {-# INLINE typeGType #-}

noRsaHashedImportParams :: Maybe RsaHashedImportParams
noRsaHashedImportParams :: Maybe RsaHashedImportParams
noRsaHashedImportParams = Maybe RsaHashedImportParams
forall a. Maybe a
Nothing
{-# INLINE noRsaHashedImportParams #-}

gTypeRsaHashedImportParams :: JSM GType
gTypeRsaHashedImportParams :: JSM GType
gTypeRsaHashedImportParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RsaHashedImportParams"

-- | Functions for this inteface are in "JSDOM.RsaHashedKeyGenParams".
-- Base interface functions are in:
--
--     * "JSDOM.RsaKeyGenParams"
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RsaHashedKeyGenParams Mozilla RsaHashedKeyGenParams documentation>
newtype RsaHashedKeyGenParams = RsaHashedKeyGenParams { RsaHashedKeyGenParams -> JSVal
unRsaHashedKeyGenParams :: JSVal }

instance PToJSVal RsaHashedKeyGenParams where
  pToJSVal :: RsaHashedKeyGenParams -> JSVal
pToJSVal = RsaHashedKeyGenParams -> JSVal
unRsaHashedKeyGenParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal RsaHashedKeyGenParams where
  pFromJSVal :: JSVal -> RsaHashedKeyGenParams
pFromJSVal = JSVal -> RsaHashedKeyGenParams
RsaHashedKeyGenParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal RsaHashedKeyGenParams where
  toJSVal :: RsaHashedKeyGenParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RsaHashedKeyGenParams -> JSVal)
-> RsaHashedKeyGenParams
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RsaHashedKeyGenParams -> JSVal
unRsaHashedKeyGenParams
  {-# INLINE toJSVal #-}

instance FromJSVal RsaHashedKeyGenParams where
  fromJSVal :: JSVal -> JSM (Maybe RsaHashedKeyGenParams)
fromJSVal JSVal
v = (JSVal -> RsaHashedKeyGenParams)
-> Maybe JSVal -> Maybe RsaHashedKeyGenParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RsaHashedKeyGenParams
RsaHashedKeyGenParams (Maybe JSVal -> Maybe RsaHashedKeyGenParams)
-> JSM (Maybe JSVal) -> JSM (Maybe RsaHashedKeyGenParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RsaHashedKeyGenParams
fromJSValUnchecked = RsaHashedKeyGenParams -> JSM RsaHashedKeyGenParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RsaHashedKeyGenParams -> JSM RsaHashedKeyGenParams)
-> (JSVal -> RsaHashedKeyGenParams)
-> JSVal
-> JSM RsaHashedKeyGenParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RsaHashedKeyGenParams
RsaHashedKeyGenParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RsaHashedKeyGenParams where
  makeObject :: RsaHashedKeyGenParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RsaHashedKeyGenParams -> JSVal)
-> RsaHashedKeyGenParams
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RsaHashedKeyGenParams -> JSVal
unRsaHashedKeyGenParams

instance IsRsaKeyGenParams RsaHashedKeyGenParams
instance IsCryptoAlgorithmParameters RsaHashedKeyGenParams
instance IsGObject RsaHashedKeyGenParams where
  typeGType :: RsaHashedKeyGenParams -> JSM GType
typeGType RsaHashedKeyGenParams
_ = JSM GType
gTypeRsaHashedKeyGenParams
  {-# INLINE typeGType #-}

noRsaHashedKeyGenParams :: Maybe RsaHashedKeyGenParams
noRsaHashedKeyGenParams :: Maybe RsaHashedKeyGenParams
noRsaHashedKeyGenParams = Maybe RsaHashedKeyGenParams
forall a. Maybe a
Nothing
{-# INLINE noRsaHashedKeyGenParams #-}

gTypeRsaHashedKeyGenParams :: JSM GType
gTypeRsaHashedKeyGenParams :: JSM GType
gTypeRsaHashedKeyGenParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RsaHashedKeyGenParams"

-- | Functions for this inteface are in "JSDOM.RsaKeyGenParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RsaKeyGenParams Mozilla RsaKeyGenParams documentation>
newtype RsaKeyGenParams = RsaKeyGenParams { RsaKeyGenParams -> JSVal
unRsaKeyGenParams :: JSVal }

instance PToJSVal RsaKeyGenParams where
  pToJSVal :: RsaKeyGenParams -> JSVal
pToJSVal = RsaKeyGenParams -> JSVal
unRsaKeyGenParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal RsaKeyGenParams where
  pFromJSVal :: JSVal -> RsaKeyGenParams
pFromJSVal = JSVal -> RsaKeyGenParams
RsaKeyGenParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal RsaKeyGenParams where
  toJSVal :: RsaKeyGenParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RsaKeyGenParams -> JSVal) -> RsaKeyGenParams -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RsaKeyGenParams -> JSVal
unRsaKeyGenParams
  {-# INLINE toJSVal #-}

instance FromJSVal RsaKeyGenParams where
  fromJSVal :: JSVal -> JSM (Maybe RsaKeyGenParams)
fromJSVal JSVal
v = (JSVal -> RsaKeyGenParams) -> Maybe JSVal -> Maybe RsaKeyGenParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RsaKeyGenParams
RsaKeyGenParams (Maybe JSVal -> Maybe RsaKeyGenParams)
-> JSM (Maybe JSVal) -> JSM (Maybe RsaKeyGenParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RsaKeyGenParams
fromJSValUnchecked = RsaKeyGenParams -> JSM RsaKeyGenParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RsaKeyGenParams -> JSM RsaKeyGenParams)
-> (JSVal -> RsaKeyGenParams) -> JSVal -> JSM RsaKeyGenParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RsaKeyGenParams
RsaKeyGenParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RsaKeyGenParams where
  makeObject :: RsaKeyGenParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RsaKeyGenParams -> JSVal) -> RsaKeyGenParams -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RsaKeyGenParams -> JSVal
unRsaKeyGenParams

class (IsCryptoAlgorithmParameters o, IsGObject o) => IsRsaKeyGenParams o
toRsaKeyGenParams :: IsRsaKeyGenParams o => o -> RsaKeyGenParams
toRsaKeyGenParams :: forall o. IsRsaKeyGenParams o => o -> RsaKeyGenParams
toRsaKeyGenParams = JSVal -> RsaKeyGenParams
RsaKeyGenParams (JSVal -> RsaKeyGenParams) -> (o -> JSVal) -> o -> RsaKeyGenParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsRsaKeyGenParams RsaKeyGenParams
instance IsCryptoAlgorithmParameters RsaKeyGenParams
instance IsGObject RsaKeyGenParams where
  typeGType :: RsaKeyGenParams -> JSM GType
typeGType RsaKeyGenParams
_ = JSM GType
gTypeRsaKeyGenParams
  {-# INLINE typeGType #-}

noRsaKeyGenParams :: Maybe RsaKeyGenParams
noRsaKeyGenParams :: Maybe RsaKeyGenParams
noRsaKeyGenParams = Maybe RsaKeyGenParams
forall a. Maybe a
Nothing
{-# INLINE noRsaKeyGenParams #-}

gTypeRsaKeyGenParams :: JSM GType
gTypeRsaKeyGenParams :: JSM GType
gTypeRsaKeyGenParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RsaKeyGenParams"

-- | Functions for this inteface are in "JSDOM.RsaOaepParams".
-- Base interface functions are in:
--
--     * "JSDOM.CryptoAlgorithmParameters"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RsaOaepParams Mozilla RsaOaepParams documentation>
newtype RsaOaepParams = RsaOaepParams { RsaOaepParams -> JSVal
unRsaOaepParams :: JSVal }

instance PToJSVal RsaOaepParams where
  pToJSVal :: RsaOaepParams -> JSVal
pToJSVal = RsaOaepParams -> JSVal
unRsaOaepParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal RsaOaepParams where
  pFromJSVal :: JSVal -> RsaOaepParams
pFromJSVal = JSVal -> RsaOaepParams
RsaOaepParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal RsaOaepParams where
  toJSVal :: RsaOaepParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RsaOaepParams -> JSVal) -> RsaOaepParams -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RsaOaepParams -> JSVal
unRsaOaepParams
  {-# INLINE toJSVal #-}

instance FromJSVal RsaOaepParams where
  fromJSVal :: JSVal -> JSM (Maybe RsaOaepParams)
fromJSVal JSVal
v = (JSVal -> RsaOaepParams) -> Maybe JSVal -> Maybe RsaOaepParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RsaOaepParams
RsaOaepParams (Maybe JSVal -> Maybe RsaOaepParams)
-> JSM (Maybe JSVal) -> JSM (Maybe RsaOaepParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RsaOaepParams
fromJSValUnchecked = RsaOaepParams -> JSM RsaOaepParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RsaOaepParams -> JSM RsaOaepParams)
-> (JSVal -> RsaOaepParams) -> JSVal -> JSM RsaOaepParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RsaOaepParams
RsaOaepParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RsaOaepParams where
  makeObject :: RsaOaepParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RsaOaepParams -> JSVal) -> RsaOaepParams -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RsaOaepParams -> JSVal
unRsaOaepParams

instance IsCryptoAlgorithmParameters RsaOaepParams
instance IsGObject RsaOaepParams where
  typeGType :: RsaOaepParams -> JSM GType
typeGType RsaOaepParams
_ = JSM GType
gTypeRsaOaepParams
  {-# INLINE typeGType #-}

noRsaOaepParams :: Maybe RsaOaepParams
noRsaOaepParams :: Maybe RsaOaepParams
noRsaOaepParams = Maybe RsaOaepParams
forall a. Maybe a
Nothing
{-# INLINE noRsaOaepParams #-}

gTypeRsaOaepParams :: JSM GType
gTypeRsaOaepParams :: JSM GType
gTypeRsaOaepParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RsaOaepParams"

-- | Functions for this inteface are in "JSDOM.RsaOtherPrimesInfo".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/RsaOtherPrimesInfo Mozilla RsaOtherPrimesInfo documentation>
newtype RsaOtherPrimesInfo = RsaOtherPrimesInfo { RsaOtherPrimesInfo -> JSVal
unRsaOtherPrimesInfo :: JSVal }

instance PToJSVal RsaOtherPrimesInfo where
  pToJSVal :: RsaOtherPrimesInfo -> JSVal
pToJSVal = RsaOtherPrimesInfo -> JSVal
unRsaOtherPrimesInfo
  {-# INLINE pToJSVal #-}

instance PFromJSVal RsaOtherPrimesInfo where
  pFromJSVal :: JSVal -> RsaOtherPrimesInfo
pFromJSVal = JSVal -> RsaOtherPrimesInfo
RsaOtherPrimesInfo
  {-# INLINE pFromJSVal #-}

instance ToJSVal RsaOtherPrimesInfo where
  toJSVal :: RsaOtherPrimesInfo -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (RsaOtherPrimesInfo -> JSVal) -> RsaOtherPrimesInfo -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RsaOtherPrimesInfo -> JSVal
unRsaOtherPrimesInfo
  {-# INLINE toJSVal #-}

instance FromJSVal RsaOtherPrimesInfo where
  fromJSVal :: JSVal -> JSM (Maybe RsaOtherPrimesInfo)
fromJSVal JSVal
v = (JSVal -> RsaOtherPrimesInfo)
-> Maybe JSVal -> Maybe RsaOtherPrimesInfo
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> RsaOtherPrimesInfo
RsaOtherPrimesInfo (Maybe JSVal -> Maybe RsaOtherPrimesInfo)
-> JSM (Maybe JSVal) -> JSM (Maybe RsaOtherPrimesInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM RsaOtherPrimesInfo
fromJSValUnchecked = RsaOtherPrimesInfo -> JSM RsaOtherPrimesInfo
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (RsaOtherPrimesInfo -> JSM RsaOtherPrimesInfo)
-> (JSVal -> RsaOtherPrimesInfo) -> JSVal -> JSM RsaOtherPrimesInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> RsaOtherPrimesInfo
RsaOtherPrimesInfo
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject RsaOtherPrimesInfo where
  makeObject :: RsaOtherPrimesInfo -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (RsaOtherPrimesInfo -> JSVal)
-> RsaOtherPrimesInfo
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RsaOtherPrimesInfo -> JSVal
unRsaOtherPrimesInfo

instance IsGObject RsaOtherPrimesInfo where
  typeGType :: RsaOtherPrimesInfo -> JSM GType
typeGType RsaOtherPrimesInfo
_ = JSM GType
gTypeRsaOtherPrimesInfo
  {-# INLINE typeGType #-}

noRsaOtherPrimesInfo :: Maybe RsaOtherPrimesInfo
noRsaOtherPrimesInfo :: Maybe RsaOtherPrimesInfo
noRsaOtherPrimesInfo = Maybe RsaOtherPrimesInfo
forall a. Maybe a
Nothing
{-# INLINE noRsaOtherPrimesInfo #-}

gTypeRsaOtherPrimesInfo :: JSM GType
gTypeRsaOtherPrimesInfo :: JSM GType
gTypeRsaOtherPrimesInfo = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"RsaOtherPrimesInfo"

-- | Functions for this inteface are in "JSDOM.SQLError".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SQLError Mozilla SQLError documentation>
newtype SQLError = SQLError { SQLError -> JSVal
unSQLError :: JSVal }

instance PToJSVal SQLError where
  pToJSVal :: SQLError -> JSVal
pToJSVal = SQLError -> JSVal
unSQLError
  {-# INLINE pToJSVal #-}

instance PFromJSVal SQLError where
  pFromJSVal :: JSVal -> SQLError
pFromJSVal = JSVal -> SQLError
SQLError
  {-# INLINE pFromJSVal #-}

instance ToJSVal SQLError where
  toJSVal :: SQLError -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SQLError -> JSVal) -> SQLError -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLError -> JSVal
unSQLError
  {-# INLINE toJSVal #-}

instance FromJSVal SQLError where
  fromJSVal :: JSVal -> JSM (Maybe SQLError)
fromJSVal JSVal
v = (JSVal -> SQLError) -> Maybe JSVal -> Maybe SQLError
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SQLError
SQLError (Maybe JSVal -> Maybe SQLError)
-> JSM (Maybe JSVal) -> JSM (Maybe SQLError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SQLError
fromJSValUnchecked = SQLError -> JSM SQLError
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SQLError -> JSM SQLError)
-> (JSVal -> SQLError) -> JSVal -> JSM SQLError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SQLError
SQLError
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SQLError where
  makeObject :: SQLError -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SQLError -> JSVal) -> SQLError -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLError -> JSVal
unSQLError

instance IsGObject SQLError where
  typeGType :: SQLError -> JSM GType
typeGType SQLError
_ = JSM GType
gTypeSQLError
  {-# INLINE typeGType #-}

noSQLError :: Maybe SQLError
noSQLError :: Maybe SQLError
noSQLError = Maybe SQLError
forall a. Maybe a
Nothing
{-# INLINE noSQLError #-}

gTypeSQLError :: JSM GType
gTypeSQLError :: JSM GType
gTypeSQLError = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SQLError"

-- | Functions for this inteface are in "JSDOM.SQLException".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SQLException Mozilla SQLException documentation>
newtype SQLException = SQLException { SQLException -> JSVal
unSQLException :: JSVal }

instance PToJSVal SQLException where
  pToJSVal :: SQLException -> JSVal
pToJSVal = SQLException -> JSVal
unSQLException
  {-# INLINE pToJSVal #-}

instance PFromJSVal SQLException where
  pFromJSVal :: JSVal -> SQLException
pFromJSVal = JSVal -> SQLException
SQLException
  {-# INLINE pFromJSVal #-}

instance ToJSVal SQLException where
  toJSVal :: SQLException -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SQLException -> JSVal) -> SQLException -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLException -> JSVal
unSQLException
  {-# INLINE toJSVal #-}

instance FromJSVal SQLException where
  fromJSVal :: JSVal -> JSM (Maybe SQLException)
fromJSVal JSVal
v = (JSVal -> SQLException) -> Maybe JSVal -> Maybe SQLException
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SQLException
SQLException (Maybe JSVal -> Maybe SQLException)
-> JSM (Maybe JSVal) -> JSM (Maybe SQLException)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SQLException
fromJSValUnchecked = SQLException -> JSM SQLException
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SQLException -> JSM SQLException)
-> (JSVal -> SQLException) -> JSVal -> JSM SQLException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SQLException
SQLException
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SQLException where
  makeObject :: SQLException -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SQLException -> JSVal) -> SQLException -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLException -> JSVal
unSQLException

instance IsGObject SQLException where
  typeGType :: SQLException -> JSM GType
typeGType SQLException
_ = JSM GType
gTypeSQLException
  {-# INLINE typeGType #-}

noSQLException :: Maybe SQLException
noSQLException :: Maybe SQLException
noSQLException = Maybe SQLException
forall a. Maybe a
Nothing
{-# INLINE noSQLException #-}

gTypeSQLException :: JSM GType
gTypeSQLException :: JSM GType
gTypeSQLException = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SQLException"

-- | Functions for this inteface are in "JSDOM.SQLResultSet".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SQLResultSet Mozilla SQLResultSet documentation>
newtype SQLResultSet = SQLResultSet { SQLResultSet -> JSVal
unSQLResultSet :: JSVal }

instance PToJSVal SQLResultSet where
  pToJSVal :: SQLResultSet -> JSVal
pToJSVal = SQLResultSet -> JSVal
unSQLResultSet
  {-# INLINE pToJSVal #-}

instance PFromJSVal SQLResultSet where
  pFromJSVal :: JSVal -> SQLResultSet
pFromJSVal = JSVal -> SQLResultSet
SQLResultSet
  {-# INLINE pFromJSVal #-}

instance ToJSVal SQLResultSet where
  toJSVal :: SQLResultSet -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SQLResultSet -> JSVal) -> SQLResultSet -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLResultSet -> JSVal
unSQLResultSet
  {-# INLINE toJSVal #-}

instance FromJSVal SQLResultSet where
  fromJSVal :: JSVal -> JSM (Maybe SQLResultSet)
fromJSVal JSVal
v = (JSVal -> SQLResultSet) -> Maybe JSVal -> Maybe SQLResultSet
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SQLResultSet
SQLResultSet (Maybe JSVal -> Maybe SQLResultSet)
-> JSM (Maybe JSVal) -> JSM (Maybe SQLResultSet)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SQLResultSet
fromJSValUnchecked = SQLResultSet -> JSM SQLResultSet
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SQLResultSet -> JSM SQLResultSet)
-> (JSVal -> SQLResultSet) -> JSVal -> JSM SQLResultSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SQLResultSet
SQLResultSet
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SQLResultSet where
  makeObject :: SQLResultSet -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SQLResultSet -> JSVal) -> SQLResultSet -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLResultSet -> JSVal
unSQLResultSet

instance IsGObject SQLResultSet where
  typeGType :: SQLResultSet -> JSM GType
typeGType SQLResultSet
_ = JSM GType
gTypeSQLResultSet
  {-# INLINE typeGType #-}

noSQLResultSet :: Maybe SQLResultSet
noSQLResultSet :: Maybe SQLResultSet
noSQLResultSet = Maybe SQLResultSet
forall a. Maybe a
Nothing
{-# INLINE noSQLResultSet #-}

gTypeSQLResultSet :: JSM GType
gTypeSQLResultSet :: JSM GType
gTypeSQLResultSet = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SQLResultSet"

-- | Functions for this inteface are in "JSDOM.SQLResultSetRowList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SQLResultSetRowList Mozilla SQLResultSetRowList documentation>
newtype SQLResultSetRowList = SQLResultSetRowList { SQLResultSetRowList -> JSVal
unSQLResultSetRowList :: JSVal }

instance PToJSVal SQLResultSetRowList where
  pToJSVal :: SQLResultSetRowList -> JSVal
pToJSVal = SQLResultSetRowList -> JSVal
unSQLResultSetRowList
  {-# INLINE pToJSVal #-}

instance PFromJSVal SQLResultSetRowList where
  pFromJSVal :: JSVal -> SQLResultSetRowList
pFromJSVal = JSVal -> SQLResultSetRowList
SQLResultSetRowList
  {-# INLINE pFromJSVal #-}

instance ToJSVal SQLResultSetRowList where
  toJSVal :: SQLResultSetRowList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SQLResultSetRowList -> JSVal)
-> SQLResultSetRowList
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLResultSetRowList -> JSVal
unSQLResultSetRowList
  {-# INLINE toJSVal #-}

instance FromJSVal SQLResultSetRowList where
  fromJSVal :: JSVal -> JSM (Maybe SQLResultSetRowList)
fromJSVal JSVal
v = (JSVal -> SQLResultSetRowList)
-> Maybe JSVal -> Maybe SQLResultSetRowList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SQLResultSetRowList
SQLResultSetRowList (Maybe JSVal -> Maybe SQLResultSetRowList)
-> JSM (Maybe JSVal) -> JSM (Maybe SQLResultSetRowList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SQLResultSetRowList
fromJSValUnchecked = SQLResultSetRowList -> JSM SQLResultSetRowList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SQLResultSetRowList -> JSM SQLResultSetRowList)
-> (JSVal -> SQLResultSetRowList)
-> JSVal
-> JSM SQLResultSetRowList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SQLResultSetRowList
SQLResultSetRowList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SQLResultSetRowList where
  makeObject :: SQLResultSetRowList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SQLResultSetRowList -> JSVal)
-> SQLResultSetRowList
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLResultSetRowList -> JSVal
unSQLResultSetRowList

instance IsGObject SQLResultSetRowList where
  typeGType :: SQLResultSetRowList -> JSM GType
typeGType SQLResultSetRowList
_ = JSM GType
gTypeSQLResultSetRowList
  {-# INLINE typeGType #-}

noSQLResultSetRowList :: Maybe SQLResultSetRowList
noSQLResultSetRowList :: Maybe SQLResultSetRowList
noSQLResultSetRowList = Maybe SQLResultSetRowList
forall a. Maybe a
Nothing
{-# INLINE noSQLResultSetRowList #-}

gTypeSQLResultSetRowList :: JSM GType
gTypeSQLResultSetRowList :: JSM GType
gTypeSQLResultSetRowList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SQLResultSetRowList"

-- | Functions for this inteface are in "JSDOM.SQLTransaction".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SQLTransaction Mozilla SQLTransaction documentation>
newtype SQLTransaction = SQLTransaction { SQLTransaction -> JSVal
unSQLTransaction :: JSVal }

instance PToJSVal SQLTransaction where
  pToJSVal :: SQLTransaction -> JSVal
pToJSVal = SQLTransaction -> JSVal
unSQLTransaction
  {-# INLINE pToJSVal #-}

instance PFromJSVal SQLTransaction where
  pFromJSVal :: JSVal -> SQLTransaction
pFromJSVal = JSVal -> SQLTransaction
SQLTransaction
  {-# INLINE pFromJSVal #-}

instance ToJSVal SQLTransaction where
  toJSVal :: SQLTransaction -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SQLTransaction -> JSVal) -> SQLTransaction -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLTransaction -> JSVal
unSQLTransaction
  {-# INLINE toJSVal #-}

instance FromJSVal SQLTransaction where
  fromJSVal :: JSVal -> JSM (Maybe SQLTransaction)
fromJSVal JSVal
v = (JSVal -> SQLTransaction) -> Maybe JSVal -> Maybe SQLTransaction
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SQLTransaction
SQLTransaction (Maybe JSVal -> Maybe SQLTransaction)
-> JSM (Maybe JSVal) -> JSM (Maybe SQLTransaction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SQLTransaction
fromJSValUnchecked = SQLTransaction -> JSM SQLTransaction
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SQLTransaction -> JSM SQLTransaction)
-> (JSVal -> SQLTransaction) -> JSVal -> JSM SQLTransaction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SQLTransaction
SQLTransaction
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SQLTransaction where
  makeObject :: SQLTransaction -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SQLTransaction -> JSVal) -> SQLTransaction -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SQLTransaction -> JSVal
unSQLTransaction

instance IsGObject SQLTransaction where
  typeGType :: SQLTransaction -> JSM GType
typeGType SQLTransaction
_ = JSM GType
gTypeSQLTransaction
  {-# INLINE typeGType #-}

noSQLTransaction :: Maybe SQLTransaction
noSQLTransaction :: Maybe SQLTransaction
noSQLTransaction = Maybe SQLTransaction
forall a. Maybe a
Nothing
{-# INLINE noSQLTransaction #-}

gTypeSQLTransaction :: JSM GType
gTypeSQLTransaction :: JSM GType
gTypeSQLTransaction = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SQLTransaction"

-- | Functions for this inteface are in "JSDOM.SVGAElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAElement Mozilla SVGAElement documentation>
newtype SVGAElement = SVGAElement { SVGAElement -> JSVal
unSVGAElement :: JSVal }

instance PToJSVal SVGAElement where
  pToJSVal :: SVGAElement -> JSVal
pToJSVal = SVGAElement -> JSVal
unSVGAElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAElement where
  pFromJSVal :: JSVal -> SVGAElement
pFromJSVal = JSVal -> SVGAElement
SVGAElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAElement where
  toJSVal :: SVGAElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAElement -> JSVal) -> SVGAElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAElement -> JSVal
unSVGAElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGAElement)
fromJSVal JSVal
v = (JSVal -> SVGAElement) -> Maybe JSVal -> Maybe SVGAElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAElement
SVGAElement (Maybe JSVal -> Maybe SVGAElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAElement
fromJSValUnchecked = SVGAElement -> JSM SVGAElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAElement -> JSM SVGAElement)
-> (JSVal -> SVGAElement) -> JSVal -> JSM SVGAElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAElement
SVGAElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAElement where
  makeObject :: SVGAElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAElement -> JSVal) -> SVGAElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAElement -> JSVal
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 :: SVGAElement -> JSM GType
typeGType SVGAElement
_ = JSM GType
gTypeSVGAElement
  {-# INLINE typeGType #-}

noSVGAElement :: Maybe SVGAElement
noSVGAElement :: Maybe SVGAElement
noSVGAElement = Maybe SVGAElement
forall a. Maybe a
Nothing
{-# INLINE noSVGAElement #-}

gTypeSVGAElement :: JSM GType
gTypeSVGAElement :: JSM GType
gTypeSVGAElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAElement"

-- | Functions for this inteface are in "JSDOM.SVGAltGlyphDefElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAltGlyphDefElement Mozilla SVGAltGlyphDefElement documentation>
newtype SVGAltGlyphDefElement = SVGAltGlyphDefElement { SVGAltGlyphDefElement -> JSVal
unSVGAltGlyphDefElement :: JSVal }

instance PToJSVal SVGAltGlyphDefElement where
  pToJSVal :: SVGAltGlyphDefElement -> JSVal
pToJSVal = SVGAltGlyphDefElement -> JSVal
unSVGAltGlyphDefElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAltGlyphDefElement where
  pFromJSVal :: JSVal -> SVGAltGlyphDefElement
pFromJSVal = JSVal -> SVGAltGlyphDefElement
SVGAltGlyphDefElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAltGlyphDefElement where
  toJSVal :: SVGAltGlyphDefElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAltGlyphDefElement -> JSVal)
-> SVGAltGlyphDefElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAltGlyphDefElement -> JSVal
unSVGAltGlyphDefElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAltGlyphDefElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGAltGlyphDefElement)
fromJSVal JSVal
v = (JSVal -> SVGAltGlyphDefElement)
-> Maybe JSVal -> Maybe SVGAltGlyphDefElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAltGlyphDefElement
SVGAltGlyphDefElement (Maybe JSVal -> Maybe SVGAltGlyphDefElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAltGlyphDefElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAltGlyphDefElement
fromJSValUnchecked = SVGAltGlyphDefElement -> JSM SVGAltGlyphDefElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAltGlyphDefElement -> JSM SVGAltGlyphDefElement)
-> (JSVal -> SVGAltGlyphDefElement)
-> JSVal
-> JSM SVGAltGlyphDefElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAltGlyphDefElement
SVGAltGlyphDefElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAltGlyphDefElement where
  makeObject :: SVGAltGlyphDefElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAltGlyphDefElement -> JSVal)
-> SVGAltGlyphDefElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAltGlyphDefElement -> JSVal
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 :: SVGAltGlyphDefElement -> JSM GType
typeGType SVGAltGlyphDefElement
_ = JSM GType
gTypeSVGAltGlyphDefElement
  {-# INLINE typeGType #-}

noSVGAltGlyphDefElement :: Maybe SVGAltGlyphDefElement
noSVGAltGlyphDefElement :: Maybe SVGAltGlyphDefElement
noSVGAltGlyphDefElement = Maybe SVGAltGlyphDefElement
forall a. Maybe a
Nothing
{-# INLINE noSVGAltGlyphDefElement #-}

gTypeSVGAltGlyphDefElement :: JSM GType
gTypeSVGAltGlyphDefElement :: JSM GType
gTypeSVGAltGlyphDefElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAltGlyphDefElement"

-- | Functions for this inteface are in "JSDOM.SVGAltGlyphElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGTextPositioningElement"
--     * "JSDOM.SVGTextContentElement"
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--     * "JSDOM.SVGURIReference"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAltGlyphElement Mozilla SVGAltGlyphElement documentation>
newtype SVGAltGlyphElement = SVGAltGlyphElement { SVGAltGlyphElement -> JSVal
unSVGAltGlyphElement :: JSVal }

instance PToJSVal SVGAltGlyphElement where
  pToJSVal :: SVGAltGlyphElement -> JSVal
pToJSVal = SVGAltGlyphElement -> JSVal
unSVGAltGlyphElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAltGlyphElement where
  pFromJSVal :: JSVal -> SVGAltGlyphElement
pFromJSVal = JSVal -> SVGAltGlyphElement
SVGAltGlyphElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAltGlyphElement where
  toJSVal :: SVGAltGlyphElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAltGlyphElement -> JSVal) -> SVGAltGlyphElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAltGlyphElement -> JSVal
unSVGAltGlyphElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAltGlyphElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGAltGlyphElement)
fromJSVal JSVal
v = (JSVal -> SVGAltGlyphElement)
-> Maybe JSVal -> Maybe SVGAltGlyphElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAltGlyphElement
SVGAltGlyphElement (Maybe JSVal -> Maybe SVGAltGlyphElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAltGlyphElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAltGlyphElement
fromJSValUnchecked = SVGAltGlyphElement -> JSM SVGAltGlyphElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAltGlyphElement -> JSM SVGAltGlyphElement)
-> (JSVal -> SVGAltGlyphElement) -> JSVal -> JSM SVGAltGlyphElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAltGlyphElement
SVGAltGlyphElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAltGlyphElement where
  makeObject :: SVGAltGlyphElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAltGlyphElement -> JSVal)
-> SVGAltGlyphElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAltGlyphElement -> JSVal
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 :: SVGAltGlyphElement -> JSM GType
typeGType SVGAltGlyphElement
_ = JSM GType
gTypeSVGAltGlyphElement
  {-# INLINE typeGType #-}

noSVGAltGlyphElement :: Maybe SVGAltGlyphElement
noSVGAltGlyphElement :: Maybe SVGAltGlyphElement
noSVGAltGlyphElement = Maybe SVGAltGlyphElement
forall a. Maybe a
Nothing
{-# INLINE noSVGAltGlyphElement #-}

gTypeSVGAltGlyphElement :: JSM GType
gTypeSVGAltGlyphElement :: JSM GType
gTypeSVGAltGlyphElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAltGlyphElement"

-- | Functions for this inteface are in "JSDOM.SVGAltGlyphItemElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAltGlyphItemElement Mozilla SVGAltGlyphItemElement documentation>
newtype SVGAltGlyphItemElement = SVGAltGlyphItemElement { SVGAltGlyphItemElement -> JSVal
unSVGAltGlyphItemElement :: JSVal }

instance PToJSVal SVGAltGlyphItemElement where
  pToJSVal :: SVGAltGlyphItemElement -> JSVal
pToJSVal = SVGAltGlyphItemElement -> JSVal
unSVGAltGlyphItemElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAltGlyphItemElement where
  pFromJSVal :: JSVal -> SVGAltGlyphItemElement
pFromJSVal = JSVal -> SVGAltGlyphItemElement
SVGAltGlyphItemElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAltGlyphItemElement where
  toJSVal :: SVGAltGlyphItemElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAltGlyphItemElement -> JSVal)
-> SVGAltGlyphItemElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAltGlyphItemElement -> JSVal
unSVGAltGlyphItemElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAltGlyphItemElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGAltGlyphItemElement)
fromJSVal JSVal
v = (JSVal -> SVGAltGlyphItemElement)
-> Maybe JSVal -> Maybe SVGAltGlyphItemElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAltGlyphItemElement
SVGAltGlyphItemElement (Maybe JSVal -> Maybe SVGAltGlyphItemElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAltGlyphItemElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAltGlyphItemElement
fromJSValUnchecked = SVGAltGlyphItemElement -> JSM SVGAltGlyphItemElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAltGlyphItemElement -> JSM SVGAltGlyphItemElement)
-> (JSVal -> SVGAltGlyphItemElement)
-> JSVal
-> JSM SVGAltGlyphItemElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAltGlyphItemElement
SVGAltGlyphItemElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAltGlyphItemElement where
  makeObject :: SVGAltGlyphItemElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAltGlyphItemElement -> JSVal)
-> SVGAltGlyphItemElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAltGlyphItemElement -> JSVal
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 :: SVGAltGlyphItemElement -> JSM GType
typeGType SVGAltGlyphItemElement
_ = JSM GType
gTypeSVGAltGlyphItemElement
  {-# INLINE typeGType #-}

noSVGAltGlyphItemElement :: Maybe SVGAltGlyphItemElement
noSVGAltGlyphItemElement :: Maybe SVGAltGlyphItemElement
noSVGAltGlyphItemElement = Maybe SVGAltGlyphItemElement
forall a. Maybe a
Nothing
{-# INLINE noSVGAltGlyphItemElement #-}

gTypeSVGAltGlyphItemElement :: JSM GType
gTypeSVGAltGlyphItemElement :: JSM GType
gTypeSVGAltGlyphItemElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAltGlyphItemElement"

-- | Functions for this inteface are in "JSDOM.SVGAngle".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAngle Mozilla SVGAngle documentation>
newtype SVGAngle = SVGAngle { SVGAngle -> JSVal
unSVGAngle :: JSVal }

instance PToJSVal SVGAngle where
  pToJSVal :: SVGAngle -> JSVal
pToJSVal = SVGAngle -> JSVal
unSVGAngle
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAngle where
  pFromJSVal :: JSVal -> SVGAngle
pFromJSVal = JSVal -> SVGAngle
SVGAngle
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAngle where
  toJSVal :: SVGAngle -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAngle -> JSVal) -> SVGAngle -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAngle -> JSVal
unSVGAngle
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAngle where
  fromJSVal :: JSVal -> JSM (Maybe SVGAngle)
fromJSVal JSVal
v = (JSVal -> SVGAngle) -> Maybe JSVal -> Maybe SVGAngle
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAngle
SVGAngle (Maybe JSVal -> Maybe SVGAngle)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAngle)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAngle
fromJSValUnchecked = SVGAngle -> JSM SVGAngle
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAngle -> JSM SVGAngle)
-> (JSVal -> SVGAngle) -> JSVal -> JSM SVGAngle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAngle
SVGAngle
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAngle where
  makeObject :: SVGAngle -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAngle -> JSVal) -> SVGAngle -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAngle -> JSVal
unSVGAngle

instance IsGObject SVGAngle where
  typeGType :: SVGAngle -> JSM GType
typeGType SVGAngle
_ = JSM GType
gTypeSVGAngle
  {-# INLINE typeGType #-}

noSVGAngle :: Maybe SVGAngle
noSVGAngle :: Maybe SVGAngle
noSVGAngle = Maybe SVGAngle
forall a. Maybe a
Nothing
{-# INLINE noSVGAngle #-}

gTypeSVGAngle :: JSM GType
gTypeSVGAngle :: JSM GType
gTypeSVGAngle = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAngle"

-- | Functions for this inteface are in "JSDOM.SVGAnimateColorElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGAnimationElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimateColorElement Mozilla SVGAnimateColorElement documentation>
newtype SVGAnimateColorElement = SVGAnimateColorElement { SVGAnimateColorElement -> JSVal
unSVGAnimateColorElement :: JSVal }

instance PToJSVal SVGAnimateColorElement where
  pToJSVal :: SVGAnimateColorElement -> JSVal
pToJSVal = SVGAnimateColorElement -> JSVal
unSVGAnimateColorElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimateColorElement where
  pFromJSVal :: JSVal -> SVGAnimateColorElement
pFromJSVal = JSVal -> SVGAnimateColorElement
SVGAnimateColorElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimateColorElement where
  toJSVal :: SVGAnimateColorElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimateColorElement -> JSVal)
-> SVGAnimateColorElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimateColorElement -> JSVal
unSVGAnimateColorElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimateColorElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimateColorElement)
fromJSVal JSVal
v = (JSVal -> SVGAnimateColorElement)
-> Maybe JSVal -> Maybe SVGAnimateColorElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimateColorElement
SVGAnimateColorElement (Maybe JSVal -> Maybe SVGAnimateColorElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimateColorElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimateColorElement
fromJSValUnchecked = SVGAnimateColorElement -> JSM SVGAnimateColorElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimateColorElement -> JSM SVGAnimateColorElement)
-> (JSVal -> SVGAnimateColorElement)
-> JSVal
-> JSM SVGAnimateColorElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimateColorElement
SVGAnimateColorElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimateColorElement where
  makeObject :: SVGAnimateColorElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimateColorElement -> JSVal)
-> SVGAnimateColorElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimateColorElement -> JSVal
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 :: SVGAnimateColorElement -> JSM GType
typeGType SVGAnimateColorElement
_ = JSM GType
gTypeSVGAnimateColorElement
  {-# INLINE typeGType #-}

noSVGAnimateColorElement :: Maybe SVGAnimateColorElement
noSVGAnimateColorElement :: Maybe SVGAnimateColorElement
noSVGAnimateColorElement = Maybe SVGAnimateColorElement
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimateColorElement #-}

gTypeSVGAnimateColorElement :: JSM GType
gTypeSVGAnimateColorElement :: JSM GType
gTypeSVGAnimateColorElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimateColorElement"

-- | Functions for this inteface are in "JSDOM.SVGAnimateElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGAnimationElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimateElement Mozilla SVGAnimateElement documentation>
newtype SVGAnimateElement = SVGAnimateElement { SVGAnimateElement -> JSVal
unSVGAnimateElement :: JSVal }

instance PToJSVal SVGAnimateElement where
  pToJSVal :: SVGAnimateElement -> JSVal
pToJSVal = SVGAnimateElement -> JSVal
unSVGAnimateElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimateElement where
  pFromJSVal :: JSVal -> SVGAnimateElement
pFromJSVal = JSVal -> SVGAnimateElement
SVGAnimateElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimateElement where
  toJSVal :: SVGAnimateElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimateElement -> JSVal) -> SVGAnimateElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimateElement -> JSVal
unSVGAnimateElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimateElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimateElement)
fromJSVal JSVal
v = (JSVal -> SVGAnimateElement)
-> Maybe JSVal -> Maybe SVGAnimateElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimateElement
SVGAnimateElement (Maybe JSVal -> Maybe SVGAnimateElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimateElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimateElement
fromJSValUnchecked = SVGAnimateElement -> JSM SVGAnimateElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimateElement -> JSM SVGAnimateElement)
-> (JSVal -> SVGAnimateElement) -> JSVal -> JSM SVGAnimateElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimateElement
SVGAnimateElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimateElement where
  makeObject :: SVGAnimateElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimateElement -> JSVal) -> SVGAnimateElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimateElement -> JSVal
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 :: SVGAnimateElement -> JSM GType
typeGType SVGAnimateElement
_ = JSM GType
gTypeSVGAnimateElement
  {-# INLINE typeGType #-}

noSVGAnimateElement :: Maybe SVGAnimateElement
noSVGAnimateElement :: Maybe SVGAnimateElement
noSVGAnimateElement = Maybe SVGAnimateElement
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimateElement #-}

gTypeSVGAnimateElement :: JSM GType
gTypeSVGAnimateElement :: JSM GType
gTypeSVGAnimateElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimateElement"

-- | Functions for this inteface are in "JSDOM.SVGAnimateMotionElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGAnimationElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimateMotionElement Mozilla SVGAnimateMotionElement documentation>
newtype SVGAnimateMotionElement = SVGAnimateMotionElement { SVGAnimateMotionElement -> JSVal
unSVGAnimateMotionElement :: JSVal }

instance PToJSVal SVGAnimateMotionElement where
  pToJSVal :: SVGAnimateMotionElement -> JSVal
pToJSVal = SVGAnimateMotionElement -> JSVal
unSVGAnimateMotionElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimateMotionElement where
  pFromJSVal :: JSVal -> SVGAnimateMotionElement
pFromJSVal = JSVal -> SVGAnimateMotionElement
SVGAnimateMotionElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimateMotionElement where
  toJSVal :: SVGAnimateMotionElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimateMotionElement -> JSVal)
-> SVGAnimateMotionElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimateMotionElement -> JSVal
unSVGAnimateMotionElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimateMotionElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimateMotionElement)
fromJSVal JSVal
v = (JSVal -> SVGAnimateMotionElement)
-> Maybe JSVal -> Maybe SVGAnimateMotionElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimateMotionElement
SVGAnimateMotionElement (Maybe JSVal -> Maybe SVGAnimateMotionElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimateMotionElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimateMotionElement
fromJSValUnchecked = SVGAnimateMotionElement -> JSM SVGAnimateMotionElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimateMotionElement -> JSM SVGAnimateMotionElement)
-> (JSVal -> SVGAnimateMotionElement)
-> JSVal
-> JSM SVGAnimateMotionElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimateMotionElement
SVGAnimateMotionElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimateMotionElement where
  makeObject :: SVGAnimateMotionElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimateMotionElement -> JSVal)
-> SVGAnimateMotionElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimateMotionElement -> JSVal
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 :: SVGAnimateMotionElement -> JSM GType
typeGType SVGAnimateMotionElement
_ = JSM GType
gTypeSVGAnimateMotionElement
  {-# INLINE typeGType #-}

noSVGAnimateMotionElement :: Maybe SVGAnimateMotionElement
noSVGAnimateMotionElement :: Maybe SVGAnimateMotionElement
noSVGAnimateMotionElement = Maybe SVGAnimateMotionElement
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimateMotionElement #-}

gTypeSVGAnimateMotionElement :: JSM GType
gTypeSVGAnimateMotionElement :: JSM GType
gTypeSVGAnimateMotionElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimateMotionElement"

-- | Functions for this inteface are in "JSDOM.SVGAnimateTransformElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGAnimationElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimateTransformElement Mozilla SVGAnimateTransformElement documentation>
newtype SVGAnimateTransformElement = SVGAnimateTransformElement { SVGAnimateTransformElement -> JSVal
unSVGAnimateTransformElement :: JSVal }

instance PToJSVal SVGAnimateTransformElement where
  pToJSVal :: SVGAnimateTransformElement -> JSVal
pToJSVal = SVGAnimateTransformElement -> JSVal
unSVGAnimateTransformElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimateTransformElement where
  pFromJSVal :: JSVal -> SVGAnimateTransformElement
pFromJSVal = JSVal -> SVGAnimateTransformElement
SVGAnimateTransformElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimateTransformElement where
  toJSVal :: SVGAnimateTransformElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimateTransformElement -> JSVal)
-> SVGAnimateTransformElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimateTransformElement -> JSVal
unSVGAnimateTransformElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimateTransformElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimateTransformElement)
fromJSVal JSVal
v = (JSVal -> SVGAnimateTransformElement)
-> Maybe JSVal -> Maybe SVGAnimateTransformElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimateTransformElement
SVGAnimateTransformElement (Maybe JSVal -> Maybe SVGAnimateTransformElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimateTransformElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimateTransformElement
fromJSValUnchecked = SVGAnimateTransformElement -> JSM SVGAnimateTransformElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimateTransformElement -> JSM SVGAnimateTransformElement)
-> (JSVal -> SVGAnimateTransformElement)
-> JSVal
-> JSM SVGAnimateTransformElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimateTransformElement
SVGAnimateTransformElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimateTransformElement where
  makeObject :: SVGAnimateTransformElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimateTransformElement -> JSVal)
-> SVGAnimateTransformElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimateTransformElement -> JSVal
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 :: SVGAnimateTransformElement -> JSM GType
typeGType SVGAnimateTransformElement
_ = JSM GType
gTypeSVGAnimateTransformElement
  {-# INLINE typeGType #-}

noSVGAnimateTransformElement :: Maybe SVGAnimateTransformElement
noSVGAnimateTransformElement :: Maybe SVGAnimateTransformElement
noSVGAnimateTransformElement = Maybe SVGAnimateTransformElement
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimateTransformElement #-}

gTypeSVGAnimateTransformElement :: JSM GType
gTypeSVGAnimateTransformElement :: JSM GType
gTypeSVGAnimateTransformElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimateTransformElement"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedAngle".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedAngle Mozilla SVGAnimatedAngle documentation>
newtype SVGAnimatedAngle = SVGAnimatedAngle { SVGAnimatedAngle -> JSVal
unSVGAnimatedAngle :: JSVal }

instance PToJSVal SVGAnimatedAngle where
  pToJSVal :: SVGAnimatedAngle -> JSVal
pToJSVal = SVGAnimatedAngle -> JSVal
unSVGAnimatedAngle
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedAngle where
  pFromJSVal :: JSVal -> SVGAnimatedAngle
pFromJSVal = JSVal -> SVGAnimatedAngle
SVGAnimatedAngle
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedAngle where
  toJSVal :: SVGAnimatedAngle -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedAngle -> JSVal) -> SVGAnimatedAngle -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedAngle -> JSVal
unSVGAnimatedAngle
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedAngle where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedAngle)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedAngle)
-> Maybe JSVal -> Maybe SVGAnimatedAngle
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedAngle
SVGAnimatedAngle (Maybe JSVal -> Maybe SVGAnimatedAngle)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedAngle)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedAngle
fromJSValUnchecked = SVGAnimatedAngle -> JSM SVGAnimatedAngle
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedAngle -> JSM SVGAnimatedAngle)
-> (JSVal -> SVGAnimatedAngle) -> JSVal -> JSM SVGAnimatedAngle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedAngle
SVGAnimatedAngle
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedAngle where
  makeObject :: SVGAnimatedAngle -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedAngle -> JSVal) -> SVGAnimatedAngle -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedAngle -> JSVal
unSVGAnimatedAngle

instance IsGObject SVGAnimatedAngle where
  typeGType :: SVGAnimatedAngle -> JSM GType
typeGType SVGAnimatedAngle
_ = JSM GType
gTypeSVGAnimatedAngle
  {-# INLINE typeGType #-}

noSVGAnimatedAngle :: Maybe SVGAnimatedAngle
noSVGAnimatedAngle :: Maybe SVGAnimatedAngle
noSVGAnimatedAngle = Maybe SVGAnimatedAngle
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedAngle #-}

gTypeSVGAnimatedAngle :: JSM GType
gTypeSVGAnimatedAngle :: JSM GType
gTypeSVGAnimatedAngle = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedAngle"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedBoolean".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedBoolean Mozilla SVGAnimatedBoolean documentation>
newtype SVGAnimatedBoolean = SVGAnimatedBoolean { SVGAnimatedBoolean -> JSVal
unSVGAnimatedBoolean :: JSVal }

instance PToJSVal SVGAnimatedBoolean where
  pToJSVal :: SVGAnimatedBoolean -> JSVal
pToJSVal = SVGAnimatedBoolean -> JSVal
unSVGAnimatedBoolean
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedBoolean where
  pFromJSVal :: JSVal -> SVGAnimatedBoolean
pFromJSVal = JSVal -> SVGAnimatedBoolean
SVGAnimatedBoolean
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedBoolean where
  toJSVal :: SVGAnimatedBoolean -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedBoolean -> JSVal) -> SVGAnimatedBoolean -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedBoolean -> JSVal
unSVGAnimatedBoolean
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedBoolean where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedBoolean)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedBoolean)
-> Maybe JSVal -> Maybe SVGAnimatedBoolean
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedBoolean
SVGAnimatedBoolean (Maybe JSVal -> Maybe SVGAnimatedBoolean)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedBoolean)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedBoolean
fromJSValUnchecked = SVGAnimatedBoolean -> JSM SVGAnimatedBoolean
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedBoolean -> JSM SVGAnimatedBoolean)
-> (JSVal -> SVGAnimatedBoolean) -> JSVal -> JSM SVGAnimatedBoolean
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedBoolean
SVGAnimatedBoolean
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedBoolean where
  makeObject :: SVGAnimatedBoolean -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedBoolean -> JSVal)
-> SVGAnimatedBoolean
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedBoolean -> JSVal
unSVGAnimatedBoolean

instance IsGObject SVGAnimatedBoolean where
  typeGType :: SVGAnimatedBoolean -> JSM GType
typeGType SVGAnimatedBoolean
_ = JSM GType
gTypeSVGAnimatedBoolean
  {-# INLINE typeGType #-}

noSVGAnimatedBoolean :: Maybe SVGAnimatedBoolean
noSVGAnimatedBoolean :: Maybe SVGAnimatedBoolean
noSVGAnimatedBoolean = Maybe SVGAnimatedBoolean
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedBoolean #-}

gTypeSVGAnimatedBoolean :: JSM GType
gTypeSVGAnimatedBoolean :: JSM GType
gTypeSVGAnimatedBoolean = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedBoolean"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedEnumeration".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedEnumeration Mozilla SVGAnimatedEnumeration documentation>
newtype SVGAnimatedEnumeration = SVGAnimatedEnumeration { SVGAnimatedEnumeration -> JSVal
unSVGAnimatedEnumeration :: JSVal }

instance PToJSVal SVGAnimatedEnumeration where
  pToJSVal :: SVGAnimatedEnumeration -> JSVal
pToJSVal = SVGAnimatedEnumeration -> JSVal
unSVGAnimatedEnumeration
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedEnumeration where
  pFromJSVal :: JSVal -> SVGAnimatedEnumeration
pFromJSVal = JSVal -> SVGAnimatedEnumeration
SVGAnimatedEnumeration
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedEnumeration where
  toJSVal :: SVGAnimatedEnumeration -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedEnumeration -> JSVal)
-> SVGAnimatedEnumeration
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedEnumeration -> JSVal
unSVGAnimatedEnumeration
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedEnumeration where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedEnumeration)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedEnumeration)
-> Maybe JSVal -> Maybe SVGAnimatedEnumeration
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedEnumeration
SVGAnimatedEnumeration (Maybe JSVal -> Maybe SVGAnimatedEnumeration)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedEnumeration)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedEnumeration
fromJSValUnchecked = SVGAnimatedEnumeration -> JSM SVGAnimatedEnumeration
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedEnumeration -> JSM SVGAnimatedEnumeration)
-> (JSVal -> SVGAnimatedEnumeration)
-> JSVal
-> JSM SVGAnimatedEnumeration
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedEnumeration
SVGAnimatedEnumeration
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedEnumeration where
  makeObject :: SVGAnimatedEnumeration -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedEnumeration -> JSVal)
-> SVGAnimatedEnumeration
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedEnumeration -> JSVal
unSVGAnimatedEnumeration

instance IsGObject SVGAnimatedEnumeration where
  typeGType :: SVGAnimatedEnumeration -> JSM GType
typeGType SVGAnimatedEnumeration
_ = JSM GType
gTypeSVGAnimatedEnumeration
  {-# INLINE typeGType #-}

noSVGAnimatedEnumeration :: Maybe SVGAnimatedEnumeration
noSVGAnimatedEnumeration :: Maybe SVGAnimatedEnumeration
noSVGAnimatedEnumeration = Maybe SVGAnimatedEnumeration
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedEnumeration #-}

gTypeSVGAnimatedEnumeration :: JSM GType
gTypeSVGAnimatedEnumeration :: JSM GType
gTypeSVGAnimatedEnumeration = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedEnumeration"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedInteger".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedInteger Mozilla SVGAnimatedInteger documentation>
newtype SVGAnimatedInteger = SVGAnimatedInteger { SVGAnimatedInteger -> JSVal
unSVGAnimatedInteger :: JSVal }

instance PToJSVal SVGAnimatedInteger where
  pToJSVal :: SVGAnimatedInteger -> JSVal
pToJSVal = SVGAnimatedInteger -> JSVal
unSVGAnimatedInteger
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedInteger where
  pFromJSVal :: JSVal -> SVGAnimatedInteger
pFromJSVal = JSVal -> SVGAnimatedInteger
SVGAnimatedInteger
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedInteger where
  toJSVal :: SVGAnimatedInteger -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedInteger -> JSVal) -> SVGAnimatedInteger -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedInteger -> JSVal
unSVGAnimatedInteger
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedInteger where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedInteger)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedInteger)
-> Maybe JSVal -> Maybe SVGAnimatedInteger
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedInteger
SVGAnimatedInteger (Maybe JSVal -> Maybe SVGAnimatedInteger)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedInteger)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedInteger
fromJSValUnchecked = SVGAnimatedInteger -> JSM SVGAnimatedInteger
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedInteger -> JSM SVGAnimatedInteger)
-> (JSVal -> SVGAnimatedInteger) -> JSVal -> JSM SVGAnimatedInteger
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedInteger
SVGAnimatedInteger
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedInteger where
  makeObject :: SVGAnimatedInteger -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedInteger -> JSVal)
-> SVGAnimatedInteger
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedInteger -> JSVal
unSVGAnimatedInteger

instance IsGObject SVGAnimatedInteger where
  typeGType :: SVGAnimatedInteger -> JSM GType
typeGType SVGAnimatedInteger
_ = JSM GType
gTypeSVGAnimatedInteger
  {-# INLINE typeGType #-}

noSVGAnimatedInteger :: Maybe SVGAnimatedInteger
noSVGAnimatedInteger :: Maybe SVGAnimatedInteger
noSVGAnimatedInteger = Maybe SVGAnimatedInteger
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedInteger #-}

gTypeSVGAnimatedInteger :: JSM GType
gTypeSVGAnimatedInteger :: JSM GType
gTypeSVGAnimatedInteger = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedInteger"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedLength".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedLength Mozilla SVGAnimatedLength documentation>
newtype SVGAnimatedLength = SVGAnimatedLength { SVGAnimatedLength -> JSVal
unSVGAnimatedLength :: JSVal }

instance PToJSVal SVGAnimatedLength where
  pToJSVal :: SVGAnimatedLength -> JSVal
pToJSVal = SVGAnimatedLength -> JSVal
unSVGAnimatedLength
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedLength where
  pFromJSVal :: JSVal -> SVGAnimatedLength
pFromJSVal = JSVal -> SVGAnimatedLength
SVGAnimatedLength
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedLength where
  toJSVal :: SVGAnimatedLength -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedLength -> JSVal) -> SVGAnimatedLength -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedLength -> JSVal
unSVGAnimatedLength
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedLength where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedLength)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedLength)
-> Maybe JSVal -> Maybe SVGAnimatedLength
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedLength
SVGAnimatedLength (Maybe JSVal -> Maybe SVGAnimatedLength)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedLength)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedLength
fromJSValUnchecked = SVGAnimatedLength -> JSM SVGAnimatedLength
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedLength -> JSM SVGAnimatedLength)
-> (JSVal -> SVGAnimatedLength) -> JSVal -> JSM SVGAnimatedLength
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedLength
SVGAnimatedLength
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedLength where
  makeObject :: SVGAnimatedLength -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedLength -> JSVal) -> SVGAnimatedLength -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedLength -> JSVal
unSVGAnimatedLength

instance IsGObject SVGAnimatedLength where
  typeGType :: SVGAnimatedLength -> JSM GType
typeGType SVGAnimatedLength
_ = JSM GType
gTypeSVGAnimatedLength
  {-# INLINE typeGType #-}

noSVGAnimatedLength :: Maybe SVGAnimatedLength
noSVGAnimatedLength :: Maybe SVGAnimatedLength
noSVGAnimatedLength = Maybe SVGAnimatedLength
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedLength #-}

gTypeSVGAnimatedLength :: JSM GType
gTypeSVGAnimatedLength :: JSM GType
gTypeSVGAnimatedLength = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedLength"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedLengthList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedLengthList Mozilla SVGAnimatedLengthList documentation>
newtype SVGAnimatedLengthList = SVGAnimatedLengthList { SVGAnimatedLengthList -> JSVal
unSVGAnimatedLengthList :: JSVal }

instance PToJSVal SVGAnimatedLengthList where
  pToJSVal :: SVGAnimatedLengthList -> JSVal
pToJSVal = SVGAnimatedLengthList -> JSVal
unSVGAnimatedLengthList
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedLengthList where
  pFromJSVal :: JSVal -> SVGAnimatedLengthList
pFromJSVal = JSVal -> SVGAnimatedLengthList
SVGAnimatedLengthList
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedLengthList where
  toJSVal :: SVGAnimatedLengthList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedLengthList -> JSVal)
-> SVGAnimatedLengthList
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedLengthList -> JSVal
unSVGAnimatedLengthList
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedLengthList where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedLengthList)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedLengthList)
-> Maybe JSVal -> Maybe SVGAnimatedLengthList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedLengthList
SVGAnimatedLengthList (Maybe JSVal -> Maybe SVGAnimatedLengthList)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedLengthList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedLengthList
fromJSValUnchecked = SVGAnimatedLengthList -> JSM SVGAnimatedLengthList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedLengthList -> JSM SVGAnimatedLengthList)
-> (JSVal -> SVGAnimatedLengthList)
-> JSVal
-> JSM SVGAnimatedLengthList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedLengthList
SVGAnimatedLengthList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedLengthList where
  makeObject :: SVGAnimatedLengthList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedLengthList -> JSVal)
-> SVGAnimatedLengthList
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedLengthList -> JSVal
unSVGAnimatedLengthList

instance IsGObject SVGAnimatedLengthList where
  typeGType :: SVGAnimatedLengthList -> JSM GType
typeGType SVGAnimatedLengthList
_ = JSM GType
gTypeSVGAnimatedLengthList
  {-# INLINE typeGType #-}

noSVGAnimatedLengthList :: Maybe SVGAnimatedLengthList
noSVGAnimatedLengthList :: Maybe SVGAnimatedLengthList
noSVGAnimatedLengthList = Maybe SVGAnimatedLengthList
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedLengthList #-}

gTypeSVGAnimatedLengthList :: JSM GType
gTypeSVGAnimatedLengthList :: JSM GType
gTypeSVGAnimatedLengthList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedLengthList"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedNumber".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedNumber Mozilla SVGAnimatedNumber documentation>
newtype SVGAnimatedNumber = SVGAnimatedNumber { SVGAnimatedNumber -> JSVal
unSVGAnimatedNumber :: JSVal }

instance PToJSVal SVGAnimatedNumber where
  pToJSVal :: SVGAnimatedNumber -> JSVal
pToJSVal = SVGAnimatedNumber -> JSVal
unSVGAnimatedNumber
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedNumber where
  pFromJSVal :: JSVal -> SVGAnimatedNumber
pFromJSVal = JSVal -> SVGAnimatedNumber
SVGAnimatedNumber
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedNumber where
  toJSVal :: SVGAnimatedNumber -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedNumber -> JSVal) -> SVGAnimatedNumber -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedNumber -> JSVal
unSVGAnimatedNumber
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedNumber where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedNumber)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedNumber)
-> Maybe JSVal -> Maybe SVGAnimatedNumber
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedNumber
SVGAnimatedNumber (Maybe JSVal -> Maybe SVGAnimatedNumber)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedNumber)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedNumber
fromJSValUnchecked = SVGAnimatedNumber -> JSM SVGAnimatedNumber
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedNumber -> JSM SVGAnimatedNumber)
-> (JSVal -> SVGAnimatedNumber) -> JSVal -> JSM SVGAnimatedNumber
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedNumber
SVGAnimatedNumber
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedNumber where
  makeObject :: SVGAnimatedNumber -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedNumber -> JSVal) -> SVGAnimatedNumber -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedNumber -> JSVal
unSVGAnimatedNumber

instance IsGObject SVGAnimatedNumber where
  typeGType :: SVGAnimatedNumber -> JSM GType
typeGType SVGAnimatedNumber
_ = JSM GType
gTypeSVGAnimatedNumber
  {-# INLINE typeGType #-}

noSVGAnimatedNumber :: Maybe SVGAnimatedNumber
noSVGAnimatedNumber :: Maybe SVGAnimatedNumber
noSVGAnimatedNumber = Maybe SVGAnimatedNumber
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedNumber #-}

gTypeSVGAnimatedNumber :: JSM GType
gTypeSVGAnimatedNumber :: JSM GType
gTypeSVGAnimatedNumber = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedNumber"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedNumberList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedNumberList Mozilla SVGAnimatedNumberList documentation>
newtype SVGAnimatedNumberList = SVGAnimatedNumberList { SVGAnimatedNumberList -> JSVal
unSVGAnimatedNumberList :: JSVal }

instance PToJSVal SVGAnimatedNumberList where
  pToJSVal :: SVGAnimatedNumberList -> JSVal
pToJSVal = SVGAnimatedNumberList -> JSVal
unSVGAnimatedNumberList
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedNumberList where
  pFromJSVal :: JSVal -> SVGAnimatedNumberList
pFromJSVal = JSVal -> SVGAnimatedNumberList
SVGAnimatedNumberList
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedNumberList where
  toJSVal :: SVGAnimatedNumberList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedNumberList -> JSVal)
-> SVGAnimatedNumberList
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedNumberList -> JSVal
unSVGAnimatedNumberList
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedNumberList where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedNumberList)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedNumberList)
-> Maybe JSVal -> Maybe SVGAnimatedNumberList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedNumberList
SVGAnimatedNumberList (Maybe JSVal -> Maybe SVGAnimatedNumberList)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedNumberList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedNumberList
fromJSValUnchecked = SVGAnimatedNumberList -> JSM SVGAnimatedNumberList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedNumberList -> JSM SVGAnimatedNumberList)
-> (JSVal -> SVGAnimatedNumberList)
-> JSVal
-> JSM SVGAnimatedNumberList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedNumberList
SVGAnimatedNumberList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedNumberList where
  makeObject :: SVGAnimatedNumberList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedNumberList -> JSVal)
-> SVGAnimatedNumberList
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedNumberList -> JSVal
unSVGAnimatedNumberList

instance IsGObject SVGAnimatedNumberList where
  typeGType :: SVGAnimatedNumberList -> JSM GType
typeGType SVGAnimatedNumberList
_ = JSM GType
gTypeSVGAnimatedNumberList
  {-# INLINE typeGType #-}

noSVGAnimatedNumberList :: Maybe SVGAnimatedNumberList
noSVGAnimatedNumberList :: Maybe SVGAnimatedNumberList
noSVGAnimatedNumberList = Maybe SVGAnimatedNumberList
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedNumberList #-}

gTypeSVGAnimatedNumberList :: JSM GType
gTypeSVGAnimatedNumberList :: JSM GType
gTypeSVGAnimatedNumberList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedNumberList"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedPreserveAspectRatio".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedPreserveAspectRatio Mozilla SVGAnimatedPreserveAspectRatio documentation>
newtype SVGAnimatedPreserveAspectRatio = SVGAnimatedPreserveAspectRatio { SVGAnimatedPreserveAspectRatio -> JSVal
unSVGAnimatedPreserveAspectRatio :: JSVal }

instance PToJSVal SVGAnimatedPreserveAspectRatio where
  pToJSVal :: SVGAnimatedPreserveAspectRatio -> JSVal
pToJSVal = SVGAnimatedPreserveAspectRatio -> JSVal
unSVGAnimatedPreserveAspectRatio
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedPreserveAspectRatio where
  pFromJSVal :: JSVal -> SVGAnimatedPreserveAspectRatio
pFromJSVal = JSVal -> SVGAnimatedPreserveAspectRatio
SVGAnimatedPreserveAspectRatio
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedPreserveAspectRatio where
  toJSVal :: SVGAnimatedPreserveAspectRatio -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedPreserveAspectRatio -> JSVal)
-> SVGAnimatedPreserveAspectRatio
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedPreserveAspectRatio -> JSVal
unSVGAnimatedPreserveAspectRatio
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedPreserveAspectRatio where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedPreserveAspectRatio)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedPreserveAspectRatio)
-> Maybe JSVal -> Maybe SVGAnimatedPreserveAspectRatio
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedPreserveAspectRatio
SVGAnimatedPreserveAspectRatio (Maybe JSVal -> Maybe SVGAnimatedPreserveAspectRatio)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedPreserveAspectRatio)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedPreserveAspectRatio
fromJSValUnchecked = SVGAnimatedPreserveAspectRatio
-> JSM SVGAnimatedPreserveAspectRatio
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedPreserveAspectRatio
 -> JSM SVGAnimatedPreserveAspectRatio)
-> (JSVal -> SVGAnimatedPreserveAspectRatio)
-> JSVal
-> JSM SVGAnimatedPreserveAspectRatio
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedPreserveAspectRatio
SVGAnimatedPreserveAspectRatio
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedPreserveAspectRatio where
  makeObject :: SVGAnimatedPreserveAspectRatio -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedPreserveAspectRatio -> JSVal)
-> SVGAnimatedPreserveAspectRatio
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedPreserveAspectRatio -> JSVal
unSVGAnimatedPreserveAspectRatio

instance IsGObject SVGAnimatedPreserveAspectRatio where
  typeGType :: SVGAnimatedPreserveAspectRatio -> JSM GType
typeGType SVGAnimatedPreserveAspectRatio
_ = JSM GType
gTypeSVGAnimatedPreserveAspectRatio
  {-# INLINE typeGType #-}

noSVGAnimatedPreserveAspectRatio :: Maybe SVGAnimatedPreserveAspectRatio
noSVGAnimatedPreserveAspectRatio :: Maybe SVGAnimatedPreserveAspectRatio
noSVGAnimatedPreserveAspectRatio = Maybe SVGAnimatedPreserveAspectRatio
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedPreserveAspectRatio #-}

gTypeSVGAnimatedPreserveAspectRatio :: JSM GType
gTypeSVGAnimatedPreserveAspectRatio :: JSM GType
gTypeSVGAnimatedPreserveAspectRatio = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedPreserveAspectRatio"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedRect".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedRect Mozilla SVGAnimatedRect documentation>
newtype SVGAnimatedRect = SVGAnimatedRect { SVGAnimatedRect -> JSVal
unSVGAnimatedRect :: JSVal }

instance PToJSVal SVGAnimatedRect where
  pToJSVal :: SVGAnimatedRect -> JSVal
pToJSVal = SVGAnimatedRect -> JSVal
unSVGAnimatedRect
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedRect where
  pFromJSVal :: JSVal -> SVGAnimatedRect
pFromJSVal = JSVal -> SVGAnimatedRect
SVGAnimatedRect
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedRect where
  toJSVal :: SVGAnimatedRect -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedRect -> JSVal) -> SVGAnimatedRect -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedRect -> JSVal
unSVGAnimatedRect
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedRect where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedRect)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedRect) -> Maybe JSVal -> Maybe SVGAnimatedRect
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedRect
SVGAnimatedRect (Maybe JSVal -> Maybe SVGAnimatedRect)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedRect)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedRect
fromJSValUnchecked = SVGAnimatedRect -> JSM SVGAnimatedRect
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedRect -> JSM SVGAnimatedRect)
-> (JSVal -> SVGAnimatedRect) -> JSVal -> JSM SVGAnimatedRect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedRect
SVGAnimatedRect
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedRect where
  makeObject :: SVGAnimatedRect -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedRect -> JSVal) -> SVGAnimatedRect -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedRect -> JSVal
unSVGAnimatedRect

instance IsGObject SVGAnimatedRect where
  typeGType :: SVGAnimatedRect -> JSM GType
typeGType SVGAnimatedRect
_ = JSM GType
gTypeSVGAnimatedRect
  {-# INLINE typeGType #-}

noSVGAnimatedRect :: Maybe SVGAnimatedRect
noSVGAnimatedRect :: Maybe SVGAnimatedRect
noSVGAnimatedRect = Maybe SVGAnimatedRect
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedRect #-}

gTypeSVGAnimatedRect :: JSM GType
gTypeSVGAnimatedRect :: JSM GType
gTypeSVGAnimatedRect = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedRect"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedString".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedString Mozilla SVGAnimatedString documentation>
newtype SVGAnimatedString = SVGAnimatedString { SVGAnimatedString -> JSVal
unSVGAnimatedString :: JSVal }

instance PToJSVal SVGAnimatedString where
  pToJSVal :: SVGAnimatedString -> JSVal
pToJSVal = SVGAnimatedString -> JSVal
unSVGAnimatedString
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedString where
  pFromJSVal :: JSVal -> SVGAnimatedString
pFromJSVal = JSVal -> SVGAnimatedString
SVGAnimatedString
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedString where
  toJSVal :: SVGAnimatedString -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedString -> JSVal) -> SVGAnimatedString -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedString -> JSVal
unSVGAnimatedString
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedString where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedString)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedString)
-> Maybe JSVal -> Maybe SVGAnimatedString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedString
SVGAnimatedString (Maybe JSVal -> Maybe SVGAnimatedString)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedString
fromJSValUnchecked = SVGAnimatedString -> JSM SVGAnimatedString
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedString -> JSM SVGAnimatedString)
-> (JSVal -> SVGAnimatedString) -> JSVal -> JSM SVGAnimatedString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedString
SVGAnimatedString
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedString where
  makeObject :: SVGAnimatedString -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedString -> JSVal) -> SVGAnimatedString -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedString -> JSVal
unSVGAnimatedString

instance IsGObject SVGAnimatedString where
  typeGType :: SVGAnimatedString -> JSM GType
typeGType SVGAnimatedString
_ = JSM GType
gTypeSVGAnimatedString
  {-# INLINE typeGType #-}

noSVGAnimatedString :: Maybe SVGAnimatedString
noSVGAnimatedString :: Maybe SVGAnimatedString
noSVGAnimatedString = Maybe SVGAnimatedString
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedString #-}

gTypeSVGAnimatedString :: JSM GType
gTypeSVGAnimatedString :: JSM GType
gTypeSVGAnimatedString = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedString"

-- | Functions for this inteface are in "JSDOM.SVGAnimatedTransformList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimatedTransformList Mozilla SVGAnimatedTransformList documentation>
newtype SVGAnimatedTransformList = SVGAnimatedTransformList { SVGAnimatedTransformList -> JSVal
unSVGAnimatedTransformList :: JSVal }

instance PToJSVal SVGAnimatedTransformList where
  pToJSVal :: SVGAnimatedTransformList -> JSVal
pToJSVal = SVGAnimatedTransformList -> JSVal
unSVGAnimatedTransformList
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimatedTransformList where
  pFromJSVal :: JSVal -> SVGAnimatedTransformList
pFromJSVal = JSVal -> SVGAnimatedTransformList
SVGAnimatedTransformList
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimatedTransformList where
  toJSVal :: SVGAnimatedTransformList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimatedTransformList -> JSVal)
-> SVGAnimatedTransformList
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedTransformList -> JSVal
unSVGAnimatedTransformList
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimatedTransformList where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimatedTransformList)
fromJSVal JSVal
v = (JSVal -> SVGAnimatedTransformList)
-> Maybe JSVal -> Maybe SVGAnimatedTransformList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimatedTransformList
SVGAnimatedTransformList (Maybe JSVal -> Maybe SVGAnimatedTransformList)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimatedTransformList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimatedTransformList
fromJSValUnchecked = SVGAnimatedTransformList -> JSM SVGAnimatedTransformList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimatedTransformList -> JSM SVGAnimatedTransformList)
-> (JSVal -> SVGAnimatedTransformList)
-> JSVal
-> JSM SVGAnimatedTransformList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimatedTransformList
SVGAnimatedTransformList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimatedTransformList where
  makeObject :: SVGAnimatedTransformList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimatedTransformList -> JSVal)
-> SVGAnimatedTransformList
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimatedTransformList -> JSVal
unSVGAnimatedTransformList

instance IsGObject SVGAnimatedTransformList where
  typeGType :: SVGAnimatedTransformList -> JSM GType
typeGType SVGAnimatedTransformList
_ = JSM GType
gTypeSVGAnimatedTransformList
  {-# INLINE typeGType #-}

noSVGAnimatedTransformList :: Maybe SVGAnimatedTransformList
noSVGAnimatedTransformList :: Maybe SVGAnimatedTransformList
noSVGAnimatedTransformList = Maybe SVGAnimatedTransformList
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimatedTransformList #-}

gTypeSVGAnimatedTransformList :: JSM GType
gTypeSVGAnimatedTransformList :: JSM GType
gTypeSVGAnimatedTransformList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimatedTransformList"

-- | Functions for this inteface are in "JSDOM.SVGAnimationElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGAnimationElement Mozilla SVGAnimationElement documentation>
newtype SVGAnimationElement = SVGAnimationElement { SVGAnimationElement -> JSVal
unSVGAnimationElement :: JSVal }

instance PToJSVal SVGAnimationElement where
  pToJSVal :: SVGAnimationElement -> JSVal
pToJSVal = SVGAnimationElement -> JSVal
unSVGAnimationElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGAnimationElement where
  pFromJSVal :: JSVal -> SVGAnimationElement
pFromJSVal = JSVal -> SVGAnimationElement
SVGAnimationElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGAnimationElement where
  toJSVal :: SVGAnimationElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGAnimationElement -> JSVal)
-> SVGAnimationElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimationElement -> JSVal
unSVGAnimationElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGAnimationElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGAnimationElement)
fromJSVal JSVal
v = (JSVal -> SVGAnimationElement)
-> Maybe JSVal -> Maybe SVGAnimationElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGAnimationElement
SVGAnimationElement (Maybe JSVal -> Maybe SVGAnimationElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGAnimationElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGAnimationElement
fromJSValUnchecked = SVGAnimationElement -> JSM SVGAnimationElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGAnimationElement -> JSM SVGAnimationElement)
-> (JSVal -> SVGAnimationElement)
-> JSVal
-> JSM SVGAnimationElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGAnimationElement
SVGAnimationElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGAnimationElement where
  makeObject :: SVGAnimationElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGAnimationElement -> JSVal)
-> SVGAnimationElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGAnimationElement -> JSVal
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 :: forall o. IsSVGAnimationElement o => o -> SVGAnimationElement
toSVGAnimationElement = JSVal -> SVGAnimationElement
SVGAnimationElement (JSVal -> SVGAnimationElement)
-> (o -> JSVal) -> o -> SVGAnimationElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: SVGAnimationElement -> JSM GType
typeGType SVGAnimationElement
_ = JSM GType
gTypeSVGAnimationElement
  {-# INLINE typeGType #-}

noSVGAnimationElement :: Maybe SVGAnimationElement
noSVGAnimationElement :: Maybe SVGAnimationElement
noSVGAnimationElement = Maybe SVGAnimationElement
forall a. Maybe a
Nothing
{-# INLINE noSVGAnimationElement #-}

gTypeSVGAnimationElement :: JSM GType
gTypeSVGAnimationElement :: JSM GType
gTypeSVGAnimationElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGAnimationElement"

-- | Functions for this inteface are in "JSDOM.SVGCircleElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGCircleElement Mozilla SVGCircleElement documentation>
newtype SVGCircleElement = SVGCircleElement { SVGCircleElement -> JSVal
unSVGCircleElement :: JSVal }

instance PToJSVal SVGCircleElement where
  pToJSVal :: SVGCircleElement -> JSVal
pToJSVal = SVGCircleElement -> JSVal
unSVGCircleElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGCircleElement where
  pFromJSVal :: JSVal -> SVGCircleElement
pFromJSVal = JSVal -> SVGCircleElement
SVGCircleElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGCircleElement where
  toJSVal :: SVGCircleElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGCircleElement -> JSVal) -> SVGCircleElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGCircleElement -> JSVal
unSVGCircleElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGCircleElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGCircleElement)
fromJSVal JSVal
v = (JSVal -> SVGCircleElement)
-> Maybe JSVal -> Maybe SVGCircleElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGCircleElement
SVGCircleElement (Maybe JSVal -> Maybe SVGCircleElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGCircleElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGCircleElement
fromJSValUnchecked = SVGCircleElement -> JSM SVGCircleElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGCircleElement -> JSM SVGCircleElement)
-> (JSVal -> SVGCircleElement) -> JSVal -> JSM SVGCircleElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGCircleElement
SVGCircleElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGCircleElement where
  makeObject :: SVGCircleElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGCircleElement -> JSVal) -> SVGCircleElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGCircleElement -> JSVal
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 :: SVGCircleElement -> JSM GType
typeGType SVGCircleElement
_ = JSM GType
gTypeSVGCircleElement
  {-# INLINE typeGType #-}

noSVGCircleElement :: Maybe SVGCircleElement
noSVGCircleElement :: Maybe SVGCircleElement
noSVGCircleElement = Maybe SVGCircleElement
forall a. Maybe a
Nothing
{-# INLINE noSVGCircleElement #-}

gTypeSVGCircleElement :: JSM GType
gTypeSVGCircleElement :: JSM GType
gTypeSVGCircleElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGCircleElement"

-- | Functions for this inteface are in "JSDOM.SVGClipPathElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGClipPathElement Mozilla SVGClipPathElement documentation>
newtype SVGClipPathElement = SVGClipPathElement { SVGClipPathElement -> JSVal
unSVGClipPathElement :: JSVal }

instance PToJSVal SVGClipPathElement where
  pToJSVal :: SVGClipPathElement -> JSVal
pToJSVal = SVGClipPathElement -> JSVal
unSVGClipPathElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGClipPathElement where
  pFromJSVal :: JSVal -> SVGClipPathElement
pFromJSVal = JSVal -> SVGClipPathElement
SVGClipPathElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGClipPathElement where
  toJSVal :: SVGClipPathElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGClipPathElement -> JSVal) -> SVGClipPathElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGClipPathElement -> JSVal
unSVGClipPathElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGClipPathElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGClipPathElement)
fromJSVal JSVal
v = (JSVal -> SVGClipPathElement)
-> Maybe JSVal -> Maybe SVGClipPathElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGClipPathElement
SVGClipPathElement (Maybe JSVal -> Maybe SVGClipPathElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGClipPathElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGClipPathElement
fromJSValUnchecked = SVGClipPathElement -> JSM SVGClipPathElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGClipPathElement -> JSM SVGClipPathElement)
-> (JSVal -> SVGClipPathElement) -> JSVal -> JSM SVGClipPathElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGClipPathElement
SVGClipPathElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGClipPathElement where
  makeObject :: SVGClipPathElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGClipPathElement -> JSVal)
-> SVGClipPathElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGClipPathElement -> JSVal
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 :: SVGClipPathElement -> JSM GType
typeGType SVGClipPathElement
_ = JSM GType
gTypeSVGClipPathElement
  {-# INLINE typeGType #-}

noSVGClipPathElement :: Maybe SVGClipPathElement
noSVGClipPathElement :: Maybe SVGClipPathElement
noSVGClipPathElement = Maybe SVGClipPathElement
forall a. Maybe a
Nothing
{-# INLINE noSVGClipPathElement #-}

gTypeSVGClipPathElement :: JSM GType
gTypeSVGClipPathElement :: JSM GType
gTypeSVGClipPathElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGClipPathElement"

-- | Functions for this inteface are in "JSDOM.SVGComponentTransferFunctionElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGComponentTransferFunctionElement Mozilla SVGComponentTransferFunctionElement documentation>
newtype SVGComponentTransferFunctionElement = SVGComponentTransferFunctionElement { SVGComponentTransferFunctionElement -> JSVal
unSVGComponentTransferFunctionElement :: JSVal }

instance PToJSVal SVGComponentTransferFunctionElement where
  pToJSVal :: SVGComponentTransferFunctionElement -> JSVal
pToJSVal = SVGComponentTransferFunctionElement -> JSVal
unSVGComponentTransferFunctionElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGComponentTransferFunctionElement where
  pFromJSVal :: JSVal -> SVGComponentTransferFunctionElement
pFromJSVal = JSVal -> SVGComponentTransferFunctionElement
SVGComponentTransferFunctionElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGComponentTransferFunctionElement where
  toJSVal :: SVGComponentTransferFunctionElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGComponentTransferFunctionElement -> JSVal)
-> SVGComponentTransferFunctionElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGComponentTransferFunctionElement -> JSVal
unSVGComponentTransferFunctionElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGComponentTransferFunctionElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGComponentTransferFunctionElement)
fromJSVal JSVal
v = (JSVal -> SVGComponentTransferFunctionElement)
-> Maybe JSVal -> Maybe SVGComponentTransferFunctionElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGComponentTransferFunctionElement
SVGComponentTransferFunctionElement (Maybe JSVal -> Maybe SVGComponentTransferFunctionElement)
-> JSM (Maybe JSVal)
-> JSM (Maybe SVGComponentTransferFunctionElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGComponentTransferFunctionElement
fromJSValUnchecked = SVGComponentTransferFunctionElement
-> JSM SVGComponentTransferFunctionElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGComponentTransferFunctionElement
 -> JSM SVGComponentTransferFunctionElement)
-> (JSVal -> SVGComponentTransferFunctionElement)
-> JSVal
-> JSM SVGComponentTransferFunctionElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGComponentTransferFunctionElement
SVGComponentTransferFunctionElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGComponentTransferFunctionElement where
  makeObject :: SVGComponentTransferFunctionElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGComponentTransferFunctionElement -> JSVal)
-> SVGComponentTransferFunctionElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGComponentTransferFunctionElement -> JSVal
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 :: forall o.
IsSVGComponentTransferFunctionElement o =>
o -> SVGComponentTransferFunctionElement
toSVGComponentTransferFunctionElement = JSVal -> SVGComponentTransferFunctionElement
SVGComponentTransferFunctionElement (JSVal -> SVGComponentTransferFunctionElement)
-> (o -> JSVal) -> o -> SVGComponentTransferFunctionElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: SVGComponentTransferFunctionElement -> JSM GType
typeGType SVGComponentTransferFunctionElement
_ = JSM GType
gTypeSVGComponentTransferFunctionElement
  {-# INLINE typeGType #-}

noSVGComponentTransferFunctionElement :: Maybe SVGComponentTransferFunctionElement
noSVGComponentTransferFunctionElement :: Maybe SVGComponentTransferFunctionElement
noSVGComponentTransferFunctionElement = Maybe SVGComponentTransferFunctionElement
forall a. Maybe a
Nothing
{-# INLINE noSVGComponentTransferFunctionElement #-}

gTypeSVGComponentTransferFunctionElement :: JSM GType
gTypeSVGComponentTransferFunctionElement :: JSM GType
gTypeSVGComponentTransferFunctionElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGComponentTransferFunctionElement"

-- | Functions for this inteface are in "JSDOM.SVGCursorElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGCursorElement Mozilla SVGCursorElement documentation>
newtype SVGCursorElement = SVGCursorElement { SVGCursorElement -> JSVal
unSVGCursorElement :: JSVal }

instance PToJSVal SVGCursorElement where
  pToJSVal :: SVGCursorElement -> JSVal
pToJSVal = SVGCursorElement -> JSVal
unSVGCursorElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGCursorElement where
  pFromJSVal :: JSVal -> SVGCursorElement
pFromJSVal = JSVal -> SVGCursorElement
SVGCursorElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGCursorElement where
  toJSVal :: SVGCursorElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGCursorElement -> JSVal) -> SVGCursorElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGCursorElement -> JSVal
unSVGCursorElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGCursorElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGCursorElement)
fromJSVal JSVal
v = (JSVal -> SVGCursorElement)
-> Maybe JSVal -> Maybe SVGCursorElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGCursorElement
SVGCursorElement (Maybe JSVal -> Maybe SVGCursorElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGCursorElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGCursorElement
fromJSValUnchecked = SVGCursorElement -> JSM SVGCursorElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGCursorElement -> JSM SVGCursorElement)
-> (JSVal -> SVGCursorElement) -> JSVal -> JSM SVGCursorElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGCursorElement
SVGCursorElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGCursorElement where
  makeObject :: SVGCursorElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGCursorElement -> JSVal) -> SVGCursorElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGCursorElement -> JSVal
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 :: SVGCursorElement -> JSM GType
typeGType SVGCursorElement
_ = JSM GType
gTypeSVGCursorElement
  {-# INLINE typeGType #-}

noSVGCursorElement :: Maybe SVGCursorElement
noSVGCursorElement :: Maybe SVGCursorElement
noSVGCursorElement = Maybe SVGCursorElement
forall a. Maybe a
Nothing
{-# INLINE noSVGCursorElement #-}

gTypeSVGCursorElement :: JSM GType
gTypeSVGCursorElement :: JSM GType
gTypeSVGCursorElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGCursorElement"

-- | Functions for this inteface are in "JSDOM.SVGDefsElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGDefsElement Mozilla SVGDefsElement documentation>
newtype SVGDefsElement = SVGDefsElement { SVGDefsElement -> JSVal
unSVGDefsElement :: JSVal }

instance PToJSVal SVGDefsElement where
  pToJSVal :: SVGDefsElement -> JSVal
pToJSVal = SVGDefsElement -> JSVal
unSVGDefsElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGDefsElement where
  pFromJSVal :: JSVal -> SVGDefsElement
pFromJSVal = JSVal -> SVGDefsElement
SVGDefsElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGDefsElement where
  toJSVal :: SVGDefsElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGDefsElement -> JSVal) -> SVGDefsElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGDefsElement -> JSVal
unSVGDefsElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGDefsElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGDefsElement)
fromJSVal JSVal
v = (JSVal -> SVGDefsElement) -> Maybe JSVal -> Maybe SVGDefsElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGDefsElement
SVGDefsElement (Maybe JSVal -> Maybe SVGDefsElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGDefsElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGDefsElement
fromJSValUnchecked = SVGDefsElement -> JSM SVGDefsElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGDefsElement -> JSM SVGDefsElement)
-> (JSVal -> SVGDefsElement) -> JSVal -> JSM SVGDefsElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGDefsElement
SVGDefsElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGDefsElement where
  makeObject :: SVGDefsElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGDefsElement -> JSVal) -> SVGDefsElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGDefsElement -> JSVal
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 :: SVGDefsElement -> JSM GType
typeGType SVGDefsElement
_ = JSM GType
gTypeSVGDefsElement
  {-# INLINE typeGType #-}

noSVGDefsElement :: Maybe SVGDefsElement
noSVGDefsElement :: Maybe SVGDefsElement
noSVGDefsElement = Maybe SVGDefsElement
forall a. Maybe a
Nothing
{-# INLINE noSVGDefsElement #-}

gTypeSVGDefsElement :: JSM GType
gTypeSVGDefsElement :: JSM GType
gTypeSVGDefsElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGDefsElement"

-- | Functions for this inteface are in "JSDOM.SVGDescElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGDescElement Mozilla SVGDescElement documentation>
newtype SVGDescElement = SVGDescElement { SVGDescElement -> JSVal
unSVGDescElement :: JSVal }

instance PToJSVal SVGDescElement where
  pToJSVal :: SVGDescElement -> JSVal
pToJSVal = SVGDescElement -> JSVal
unSVGDescElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGDescElement where
  pFromJSVal :: JSVal -> SVGDescElement
pFromJSVal = JSVal -> SVGDescElement
SVGDescElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGDescElement where
  toJSVal :: SVGDescElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGDescElement -> JSVal) -> SVGDescElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGDescElement -> JSVal
unSVGDescElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGDescElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGDescElement)
fromJSVal JSVal
v = (JSVal -> SVGDescElement) -> Maybe JSVal -> Maybe SVGDescElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGDescElement
SVGDescElement (Maybe JSVal -> Maybe SVGDescElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGDescElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGDescElement
fromJSValUnchecked = SVGDescElement -> JSM SVGDescElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGDescElement -> JSM SVGDescElement)
-> (JSVal -> SVGDescElement) -> JSVal -> JSM SVGDescElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGDescElement
SVGDescElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGDescElement where
  makeObject :: SVGDescElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGDescElement -> JSVal) -> SVGDescElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGDescElement -> JSVal
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 :: SVGDescElement -> JSM GType
typeGType SVGDescElement
_ = JSM GType
gTypeSVGDescElement
  {-# INLINE typeGType #-}

noSVGDescElement :: Maybe SVGDescElement
noSVGDescElement :: Maybe SVGDescElement
noSVGDescElement = Maybe SVGDescElement
forall a. Maybe a
Nothing
{-# INLINE noSVGDescElement #-}

gTypeSVGDescElement :: JSM GType
gTypeSVGDescElement :: JSM GType
gTypeSVGDescElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGDescElement"

-- | Functions for this inteface are in "JSDOM.SVGElement".
-- Base interface functions are in:
--
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGElement Mozilla SVGElement documentation>
newtype SVGElement = SVGElement { SVGElement -> JSVal
unSVGElement :: JSVal }

instance PToJSVal SVGElement where
  pToJSVal :: SVGElement -> JSVal
pToJSVal = SVGElement -> JSVal
unSVGElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGElement where
  pFromJSVal :: JSVal -> SVGElement
pFromJSVal = JSVal -> SVGElement
SVGElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGElement where
  toJSVal :: SVGElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGElement -> JSVal) -> SVGElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGElement -> JSVal
unSVGElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGElement)
fromJSVal JSVal
v = (JSVal -> SVGElement) -> Maybe JSVal -> Maybe SVGElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGElement
SVGElement (Maybe JSVal -> Maybe SVGElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGElement
fromJSValUnchecked = SVGElement -> JSM SVGElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGElement -> JSM SVGElement)
-> (JSVal -> SVGElement) -> JSVal -> JSM SVGElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGElement
SVGElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGElement where
  makeObject :: SVGElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGElement -> JSVal) -> SVGElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGElement -> JSVal
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 :: forall o. IsSVGElement o => o -> SVGElement
toSVGElement = JSVal -> SVGElement
SVGElement (JSVal -> SVGElement) -> (o -> JSVal) -> o -> SVGElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: SVGElement -> JSM GType
typeGType SVGElement
_ = JSM GType
gTypeSVGElement
  {-# INLINE typeGType #-}

noSVGElement :: Maybe SVGElement
noSVGElement :: Maybe SVGElement
noSVGElement = Maybe SVGElement
forall a. Maybe a
Nothing
{-# INLINE noSVGElement #-}

gTypeSVGElement :: JSM GType
gTypeSVGElement :: JSM GType
gTypeSVGElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGElement"

-- | Functions for this inteface are in "JSDOM.SVGEllipseElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGEllipseElement Mozilla SVGEllipseElement documentation>
newtype SVGEllipseElement = SVGEllipseElement { SVGEllipseElement -> JSVal
unSVGEllipseElement :: JSVal }

instance PToJSVal SVGEllipseElement where
  pToJSVal :: SVGEllipseElement -> JSVal
pToJSVal = SVGEllipseElement -> JSVal
unSVGEllipseElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGEllipseElement where
  pFromJSVal :: JSVal -> SVGEllipseElement
pFromJSVal = JSVal -> SVGEllipseElement
SVGEllipseElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGEllipseElement where
  toJSVal :: SVGEllipseElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGEllipseElement -> JSVal) -> SVGEllipseElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGEllipseElement -> JSVal
unSVGEllipseElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGEllipseElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGEllipseElement)
fromJSVal JSVal
v = (JSVal -> SVGEllipseElement)
-> Maybe JSVal -> Maybe SVGEllipseElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGEllipseElement
SVGEllipseElement (Maybe JSVal -> Maybe SVGEllipseElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGEllipseElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGEllipseElement
fromJSValUnchecked = SVGEllipseElement -> JSM SVGEllipseElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGEllipseElement -> JSM SVGEllipseElement)
-> (JSVal -> SVGEllipseElement) -> JSVal -> JSM SVGEllipseElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGEllipseElement
SVGEllipseElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGEllipseElement where
  makeObject :: SVGEllipseElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGEllipseElement -> JSVal) -> SVGEllipseElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGEllipseElement -> JSVal
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 :: SVGEllipseElement -> JSM GType
typeGType SVGEllipseElement
_ = JSM GType
gTypeSVGEllipseElement
  {-# INLINE typeGType #-}

noSVGEllipseElement :: Maybe SVGEllipseElement
noSVGEllipseElement :: Maybe SVGEllipseElement
noSVGEllipseElement = Maybe SVGEllipseElement
forall a. Maybe a
Nothing
{-# INLINE noSVGEllipseElement #-}

gTypeSVGEllipseElement :: JSM GType
gTypeSVGEllipseElement :: JSM GType
gTypeSVGEllipseElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGEllipseElement"

-- | Functions for this inteface are in "JSDOM.SVGException".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGException Mozilla SVGException documentation>
newtype SVGException = SVGException { SVGException -> JSVal
unSVGException :: JSVal }

instance PToJSVal SVGException where
  pToJSVal :: SVGException -> JSVal
pToJSVal = SVGException -> JSVal
unSVGException
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGException where
  pFromJSVal :: JSVal -> SVGException
pFromJSVal = JSVal -> SVGException
SVGException
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGException where
  toJSVal :: SVGException -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGException -> JSVal) -> SVGException -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGException -> JSVal
unSVGException
  {-# INLINE toJSVal #-}

instance FromJSVal SVGException where
  fromJSVal :: JSVal -> JSM (Maybe SVGException)
fromJSVal JSVal
v = (JSVal -> SVGException) -> Maybe JSVal -> Maybe SVGException
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGException
SVGException (Maybe JSVal -> Maybe SVGException)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGException)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGException
fromJSValUnchecked = SVGException -> JSM SVGException
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGException -> JSM SVGException)
-> (JSVal -> SVGException) -> JSVal -> JSM SVGException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGException
SVGException
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGException where
  makeObject :: SVGException -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGException -> JSVal) -> SVGException -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGException -> JSVal
unSVGException

instance IsGObject SVGException where
  typeGType :: SVGException -> JSM GType
typeGType SVGException
_ = JSM GType
gTypeSVGException
  {-# INLINE typeGType #-}

noSVGException :: Maybe SVGException
noSVGException :: Maybe SVGException
noSVGException = Maybe SVGException
forall a. Maybe a
Nothing
{-# INLINE noSVGException #-}

gTypeSVGException :: JSM GType
gTypeSVGException :: JSM GType
gTypeSVGException = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGException"

-- | Functions for this inteface are in "JSDOM.SVGExternalResourcesRequired".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGExternalResourcesRequired Mozilla SVGExternalResourcesRequired documentation>
newtype SVGExternalResourcesRequired = SVGExternalResourcesRequired { SVGExternalResourcesRequired -> JSVal
unSVGExternalResourcesRequired :: JSVal }

instance PToJSVal SVGExternalResourcesRequired where
  pToJSVal :: SVGExternalResourcesRequired -> JSVal
pToJSVal = SVGExternalResourcesRequired -> JSVal
unSVGExternalResourcesRequired
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGExternalResourcesRequired where
  pFromJSVal :: JSVal -> SVGExternalResourcesRequired
pFromJSVal = JSVal -> SVGExternalResourcesRequired
SVGExternalResourcesRequired
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGExternalResourcesRequired where
  toJSVal :: SVGExternalResourcesRequired -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGExternalResourcesRequired -> JSVal)
-> SVGExternalResourcesRequired
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGExternalResourcesRequired -> JSVal
unSVGExternalResourcesRequired
  {-# INLINE toJSVal #-}

instance FromJSVal SVGExternalResourcesRequired where
  fromJSVal :: JSVal -> JSM (Maybe SVGExternalResourcesRequired)
fromJSVal JSVal
v = (JSVal -> SVGExternalResourcesRequired)
-> Maybe JSVal -> Maybe SVGExternalResourcesRequired
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGExternalResourcesRequired
SVGExternalResourcesRequired (Maybe JSVal -> Maybe SVGExternalResourcesRequired)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGExternalResourcesRequired)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGExternalResourcesRequired
fromJSValUnchecked = SVGExternalResourcesRequired -> JSM SVGExternalResourcesRequired
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGExternalResourcesRequired -> JSM SVGExternalResourcesRequired)
-> (JSVal -> SVGExternalResourcesRequired)
-> JSVal
-> JSM SVGExternalResourcesRequired
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGExternalResourcesRequired
SVGExternalResourcesRequired
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGExternalResourcesRequired where
  makeObject :: SVGExternalResourcesRequired -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGExternalResourcesRequired -> JSVal)
-> SVGExternalResourcesRequired
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGExternalResourcesRequired -> JSVal
unSVGExternalResourcesRequired

class (IsGObject o) => IsSVGExternalResourcesRequired o
toSVGExternalResourcesRequired :: IsSVGExternalResourcesRequired o => o -> SVGExternalResourcesRequired
toSVGExternalResourcesRequired :: forall o.
IsSVGExternalResourcesRequired o =>
o -> SVGExternalResourcesRequired
toSVGExternalResourcesRequired = JSVal -> SVGExternalResourcesRequired
SVGExternalResourcesRequired (JSVal -> SVGExternalResourcesRequired)
-> (o -> JSVal) -> o -> SVGExternalResourcesRequired
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsSVGExternalResourcesRequired SVGExternalResourcesRequired
instance IsGObject SVGExternalResourcesRequired where
  typeGType :: SVGExternalResourcesRequired -> JSM GType
typeGType SVGExternalResourcesRequired
_ = JSM GType
gTypeSVGExternalResourcesRequired
  {-# INLINE typeGType #-}

noSVGExternalResourcesRequired :: Maybe SVGExternalResourcesRequired
noSVGExternalResourcesRequired :: Maybe SVGExternalResourcesRequired
noSVGExternalResourcesRequired = Maybe SVGExternalResourcesRequired
forall a. Maybe a
Nothing
{-# INLINE noSVGExternalResourcesRequired #-}

gTypeSVGExternalResourcesRequired :: JSM GType
gTypeSVGExternalResourcesRequired :: JSM GType
gTypeSVGExternalResourcesRequired = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGExternalResourcesRequired"

-- | Functions for this inteface are in "JSDOM.SVGFEBlendElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEBlendElement Mozilla SVGFEBlendElement documentation>
newtype SVGFEBlendElement = SVGFEBlendElement { SVGFEBlendElement -> JSVal
unSVGFEBlendElement :: JSVal }

instance PToJSVal SVGFEBlendElement where
  pToJSVal :: SVGFEBlendElement -> JSVal
pToJSVal = SVGFEBlendElement -> JSVal
unSVGFEBlendElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEBlendElement where
  pFromJSVal :: JSVal -> SVGFEBlendElement
pFromJSVal = JSVal -> SVGFEBlendElement
SVGFEBlendElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEBlendElement where
  toJSVal :: SVGFEBlendElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEBlendElement -> JSVal) -> SVGFEBlendElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEBlendElement -> JSVal
unSVGFEBlendElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEBlendElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEBlendElement)
fromJSVal JSVal
v = (JSVal -> SVGFEBlendElement)
-> Maybe JSVal -> Maybe SVGFEBlendElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEBlendElement
SVGFEBlendElement (Maybe JSVal -> Maybe SVGFEBlendElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEBlendElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEBlendElement
fromJSValUnchecked = SVGFEBlendElement -> JSM SVGFEBlendElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEBlendElement -> JSM SVGFEBlendElement)
-> (JSVal -> SVGFEBlendElement) -> JSVal -> JSM SVGFEBlendElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEBlendElement
SVGFEBlendElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEBlendElement where
  makeObject :: SVGFEBlendElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEBlendElement -> JSVal) -> SVGFEBlendElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEBlendElement -> JSVal
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 :: SVGFEBlendElement -> JSM GType
typeGType SVGFEBlendElement
_ = JSM GType
gTypeSVGFEBlendElement
  {-# INLINE typeGType #-}

noSVGFEBlendElement :: Maybe SVGFEBlendElement
noSVGFEBlendElement :: Maybe SVGFEBlendElement
noSVGFEBlendElement = Maybe SVGFEBlendElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEBlendElement #-}

gTypeSVGFEBlendElement :: JSM GType
gTypeSVGFEBlendElement :: JSM GType
gTypeSVGFEBlendElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEBlendElement"

-- | Functions for this inteface are in "JSDOM.SVGFEColorMatrixElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEColorMatrixElement Mozilla SVGFEColorMatrixElement documentation>
newtype SVGFEColorMatrixElement = SVGFEColorMatrixElement { SVGFEColorMatrixElement -> JSVal
unSVGFEColorMatrixElement :: JSVal }

instance PToJSVal SVGFEColorMatrixElement where
  pToJSVal :: SVGFEColorMatrixElement -> JSVal
pToJSVal = SVGFEColorMatrixElement -> JSVal
unSVGFEColorMatrixElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEColorMatrixElement where
  pFromJSVal :: JSVal -> SVGFEColorMatrixElement
pFromJSVal = JSVal -> SVGFEColorMatrixElement
SVGFEColorMatrixElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEColorMatrixElement where
  toJSVal :: SVGFEColorMatrixElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEColorMatrixElement -> JSVal)
-> SVGFEColorMatrixElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEColorMatrixElement -> JSVal
unSVGFEColorMatrixElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEColorMatrixElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEColorMatrixElement)
fromJSVal JSVal
v = (JSVal -> SVGFEColorMatrixElement)
-> Maybe JSVal -> Maybe SVGFEColorMatrixElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEColorMatrixElement
SVGFEColorMatrixElement (Maybe JSVal -> Maybe SVGFEColorMatrixElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEColorMatrixElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEColorMatrixElement
fromJSValUnchecked = SVGFEColorMatrixElement -> JSM SVGFEColorMatrixElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEColorMatrixElement -> JSM SVGFEColorMatrixElement)
-> (JSVal -> SVGFEColorMatrixElement)
-> JSVal
-> JSM SVGFEColorMatrixElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEColorMatrixElement
SVGFEColorMatrixElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEColorMatrixElement where
  makeObject :: SVGFEColorMatrixElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEColorMatrixElement -> JSVal)
-> SVGFEColorMatrixElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEColorMatrixElement -> JSVal
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 :: SVGFEColorMatrixElement -> JSM GType
typeGType SVGFEColorMatrixElement
_ = JSM GType
gTypeSVGFEColorMatrixElement
  {-# INLINE typeGType #-}

noSVGFEColorMatrixElement :: Maybe SVGFEColorMatrixElement
noSVGFEColorMatrixElement :: Maybe SVGFEColorMatrixElement
noSVGFEColorMatrixElement = Maybe SVGFEColorMatrixElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEColorMatrixElement #-}

gTypeSVGFEColorMatrixElement :: JSM GType
gTypeSVGFEColorMatrixElement :: JSM GType
gTypeSVGFEColorMatrixElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEColorMatrixElement"

-- | Functions for this inteface are in "JSDOM.SVGFEComponentTransferElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEComponentTransferElement Mozilla SVGFEComponentTransferElement documentation>
newtype SVGFEComponentTransferElement = SVGFEComponentTransferElement { SVGFEComponentTransferElement -> JSVal
unSVGFEComponentTransferElement :: JSVal }

instance PToJSVal SVGFEComponentTransferElement where
  pToJSVal :: SVGFEComponentTransferElement -> JSVal
pToJSVal = SVGFEComponentTransferElement -> JSVal
unSVGFEComponentTransferElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEComponentTransferElement where
  pFromJSVal :: JSVal -> SVGFEComponentTransferElement
pFromJSVal = JSVal -> SVGFEComponentTransferElement
SVGFEComponentTransferElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEComponentTransferElement where
  toJSVal :: SVGFEComponentTransferElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEComponentTransferElement -> JSVal)
-> SVGFEComponentTransferElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEComponentTransferElement -> JSVal
unSVGFEComponentTransferElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEComponentTransferElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEComponentTransferElement)
fromJSVal JSVal
v = (JSVal -> SVGFEComponentTransferElement)
-> Maybe JSVal -> Maybe SVGFEComponentTransferElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEComponentTransferElement
SVGFEComponentTransferElement (Maybe JSVal -> Maybe SVGFEComponentTransferElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEComponentTransferElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEComponentTransferElement
fromJSValUnchecked = SVGFEComponentTransferElement -> JSM SVGFEComponentTransferElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEComponentTransferElement
 -> JSM SVGFEComponentTransferElement)
-> (JSVal -> SVGFEComponentTransferElement)
-> JSVal
-> JSM SVGFEComponentTransferElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEComponentTransferElement
SVGFEComponentTransferElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEComponentTransferElement where
  makeObject :: SVGFEComponentTransferElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEComponentTransferElement -> JSVal)
-> SVGFEComponentTransferElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEComponentTransferElement -> JSVal
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 :: SVGFEComponentTransferElement -> JSM GType
typeGType SVGFEComponentTransferElement
_ = JSM GType
gTypeSVGFEComponentTransferElement
  {-# INLINE typeGType #-}

noSVGFEComponentTransferElement :: Maybe SVGFEComponentTransferElement
noSVGFEComponentTransferElement :: Maybe SVGFEComponentTransferElement
noSVGFEComponentTransferElement = Maybe SVGFEComponentTransferElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEComponentTransferElement #-}

gTypeSVGFEComponentTransferElement :: JSM GType
gTypeSVGFEComponentTransferElement :: JSM GType
gTypeSVGFEComponentTransferElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEComponentTransferElement"

-- | Functions for this inteface are in "JSDOM.SVGFECompositeElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFECompositeElement Mozilla SVGFECompositeElement documentation>
newtype SVGFECompositeElement = SVGFECompositeElement { SVGFECompositeElement -> JSVal
unSVGFECompositeElement :: JSVal }

instance PToJSVal SVGFECompositeElement where
  pToJSVal :: SVGFECompositeElement -> JSVal
pToJSVal = SVGFECompositeElement -> JSVal
unSVGFECompositeElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFECompositeElement where
  pFromJSVal :: JSVal -> SVGFECompositeElement
pFromJSVal = JSVal -> SVGFECompositeElement
SVGFECompositeElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFECompositeElement where
  toJSVal :: SVGFECompositeElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFECompositeElement -> JSVal)
-> SVGFECompositeElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFECompositeElement -> JSVal
unSVGFECompositeElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFECompositeElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFECompositeElement)
fromJSVal JSVal
v = (JSVal -> SVGFECompositeElement)
-> Maybe JSVal -> Maybe SVGFECompositeElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFECompositeElement
SVGFECompositeElement (Maybe JSVal -> Maybe SVGFECompositeElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFECompositeElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFECompositeElement
fromJSValUnchecked = SVGFECompositeElement -> JSM SVGFECompositeElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFECompositeElement -> JSM SVGFECompositeElement)
-> (JSVal -> SVGFECompositeElement)
-> JSVal
-> JSM SVGFECompositeElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFECompositeElement
SVGFECompositeElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFECompositeElement where
  makeObject :: SVGFECompositeElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFECompositeElement -> JSVal)
-> SVGFECompositeElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFECompositeElement -> JSVal
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 :: SVGFECompositeElement -> JSM GType
typeGType SVGFECompositeElement
_ = JSM GType
gTypeSVGFECompositeElement
  {-# INLINE typeGType #-}

noSVGFECompositeElement :: Maybe SVGFECompositeElement
noSVGFECompositeElement :: Maybe SVGFECompositeElement
noSVGFECompositeElement = Maybe SVGFECompositeElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFECompositeElement #-}

gTypeSVGFECompositeElement :: JSM GType
gTypeSVGFECompositeElement :: JSM GType
gTypeSVGFECompositeElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFECompositeElement"

-- | Functions for this inteface are in "JSDOM.SVGFEConvolveMatrixElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEConvolveMatrixElement Mozilla SVGFEConvolveMatrixElement documentation>
newtype SVGFEConvolveMatrixElement = SVGFEConvolveMatrixElement { SVGFEConvolveMatrixElement -> JSVal
unSVGFEConvolveMatrixElement :: JSVal }

instance PToJSVal SVGFEConvolveMatrixElement where
  pToJSVal :: SVGFEConvolveMatrixElement -> JSVal
pToJSVal = SVGFEConvolveMatrixElement -> JSVal
unSVGFEConvolveMatrixElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEConvolveMatrixElement where
  pFromJSVal :: JSVal -> SVGFEConvolveMatrixElement
pFromJSVal = JSVal -> SVGFEConvolveMatrixElement
SVGFEConvolveMatrixElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEConvolveMatrixElement where
  toJSVal :: SVGFEConvolveMatrixElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEConvolveMatrixElement -> JSVal)
-> SVGFEConvolveMatrixElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEConvolveMatrixElement -> JSVal
unSVGFEConvolveMatrixElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEConvolveMatrixElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEConvolveMatrixElement)
fromJSVal JSVal
v = (JSVal -> SVGFEConvolveMatrixElement)
-> Maybe JSVal -> Maybe SVGFEConvolveMatrixElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEConvolveMatrixElement
SVGFEConvolveMatrixElement (Maybe JSVal -> Maybe SVGFEConvolveMatrixElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEConvolveMatrixElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEConvolveMatrixElement
fromJSValUnchecked = SVGFEConvolveMatrixElement -> JSM SVGFEConvolveMatrixElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEConvolveMatrixElement -> JSM SVGFEConvolveMatrixElement)
-> (JSVal -> SVGFEConvolveMatrixElement)
-> JSVal
-> JSM SVGFEConvolveMatrixElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEConvolveMatrixElement
SVGFEConvolveMatrixElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEConvolveMatrixElement where
  makeObject :: SVGFEConvolveMatrixElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEConvolveMatrixElement -> JSVal)
-> SVGFEConvolveMatrixElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEConvolveMatrixElement -> JSVal
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 :: SVGFEConvolveMatrixElement -> JSM GType
typeGType SVGFEConvolveMatrixElement
_ = JSM GType
gTypeSVGFEConvolveMatrixElement
  {-# INLINE typeGType #-}

noSVGFEConvolveMatrixElement :: Maybe SVGFEConvolveMatrixElement
noSVGFEConvolveMatrixElement :: Maybe SVGFEConvolveMatrixElement
noSVGFEConvolveMatrixElement = Maybe SVGFEConvolveMatrixElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEConvolveMatrixElement #-}

gTypeSVGFEConvolveMatrixElement :: JSM GType
gTypeSVGFEConvolveMatrixElement :: JSM GType
gTypeSVGFEConvolveMatrixElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEConvolveMatrixElement"

-- | Functions for this inteface are in "JSDOM.SVGFEDiffuseLightingElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEDiffuseLightingElement Mozilla SVGFEDiffuseLightingElement documentation>
newtype SVGFEDiffuseLightingElement = SVGFEDiffuseLightingElement { SVGFEDiffuseLightingElement -> JSVal
unSVGFEDiffuseLightingElement :: JSVal }

instance PToJSVal SVGFEDiffuseLightingElement where
  pToJSVal :: SVGFEDiffuseLightingElement -> JSVal
pToJSVal = SVGFEDiffuseLightingElement -> JSVal
unSVGFEDiffuseLightingElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEDiffuseLightingElement where
  pFromJSVal :: JSVal -> SVGFEDiffuseLightingElement
pFromJSVal = JSVal -> SVGFEDiffuseLightingElement
SVGFEDiffuseLightingElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEDiffuseLightingElement where
  toJSVal :: SVGFEDiffuseLightingElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEDiffuseLightingElement -> JSVal)
-> SVGFEDiffuseLightingElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEDiffuseLightingElement -> JSVal
unSVGFEDiffuseLightingElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEDiffuseLightingElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEDiffuseLightingElement)
fromJSVal JSVal
v = (JSVal -> SVGFEDiffuseLightingElement)
-> Maybe JSVal -> Maybe SVGFEDiffuseLightingElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEDiffuseLightingElement
SVGFEDiffuseLightingElement (Maybe JSVal -> Maybe SVGFEDiffuseLightingElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEDiffuseLightingElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEDiffuseLightingElement
fromJSValUnchecked = SVGFEDiffuseLightingElement -> JSM SVGFEDiffuseLightingElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEDiffuseLightingElement -> JSM SVGFEDiffuseLightingElement)
-> (JSVal -> SVGFEDiffuseLightingElement)
-> JSVal
-> JSM SVGFEDiffuseLightingElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEDiffuseLightingElement
SVGFEDiffuseLightingElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEDiffuseLightingElement where
  makeObject :: SVGFEDiffuseLightingElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEDiffuseLightingElement -> JSVal)
-> SVGFEDiffuseLightingElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEDiffuseLightingElement -> JSVal
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 :: SVGFEDiffuseLightingElement -> JSM GType
typeGType SVGFEDiffuseLightingElement
_ = JSM GType
gTypeSVGFEDiffuseLightingElement
  {-# INLINE typeGType #-}

noSVGFEDiffuseLightingElement :: Maybe SVGFEDiffuseLightingElement
noSVGFEDiffuseLightingElement :: Maybe SVGFEDiffuseLightingElement
noSVGFEDiffuseLightingElement = Maybe SVGFEDiffuseLightingElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEDiffuseLightingElement #-}

gTypeSVGFEDiffuseLightingElement :: JSM GType
gTypeSVGFEDiffuseLightingElement :: JSM GType
gTypeSVGFEDiffuseLightingElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEDiffuseLightingElement"

-- | Functions for this inteface are in "JSDOM.SVGFEDisplacementMapElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEDisplacementMapElement Mozilla SVGFEDisplacementMapElement documentation>
newtype SVGFEDisplacementMapElement = SVGFEDisplacementMapElement { SVGFEDisplacementMapElement -> JSVal
unSVGFEDisplacementMapElement :: JSVal }

instance PToJSVal SVGFEDisplacementMapElement where
  pToJSVal :: SVGFEDisplacementMapElement -> JSVal
pToJSVal = SVGFEDisplacementMapElement -> JSVal
unSVGFEDisplacementMapElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEDisplacementMapElement where
  pFromJSVal :: JSVal -> SVGFEDisplacementMapElement
pFromJSVal = JSVal -> SVGFEDisplacementMapElement
SVGFEDisplacementMapElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEDisplacementMapElement where
  toJSVal :: SVGFEDisplacementMapElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEDisplacementMapElement -> JSVal)
-> SVGFEDisplacementMapElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEDisplacementMapElement -> JSVal
unSVGFEDisplacementMapElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEDisplacementMapElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEDisplacementMapElement)
fromJSVal JSVal
v = (JSVal -> SVGFEDisplacementMapElement)
-> Maybe JSVal -> Maybe SVGFEDisplacementMapElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEDisplacementMapElement
SVGFEDisplacementMapElement (Maybe JSVal -> Maybe SVGFEDisplacementMapElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEDisplacementMapElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEDisplacementMapElement
fromJSValUnchecked = SVGFEDisplacementMapElement -> JSM SVGFEDisplacementMapElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEDisplacementMapElement -> JSM SVGFEDisplacementMapElement)
-> (JSVal -> SVGFEDisplacementMapElement)
-> JSVal
-> JSM SVGFEDisplacementMapElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEDisplacementMapElement
SVGFEDisplacementMapElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEDisplacementMapElement where
  makeObject :: SVGFEDisplacementMapElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEDisplacementMapElement -> JSVal)
-> SVGFEDisplacementMapElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEDisplacementMapElement -> JSVal
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 :: SVGFEDisplacementMapElement -> JSM GType
typeGType SVGFEDisplacementMapElement
_ = JSM GType
gTypeSVGFEDisplacementMapElement
  {-# INLINE typeGType #-}

noSVGFEDisplacementMapElement :: Maybe SVGFEDisplacementMapElement
noSVGFEDisplacementMapElement :: Maybe SVGFEDisplacementMapElement
noSVGFEDisplacementMapElement = Maybe SVGFEDisplacementMapElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEDisplacementMapElement #-}

gTypeSVGFEDisplacementMapElement :: JSM GType
gTypeSVGFEDisplacementMapElement :: JSM GType
gTypeSVGFEDisplacementMapElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEDisplacementMapElement"

-- | Functions for this inteface are in "JSDOM.SVGFEDistantLightElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEDistantLightElement Mozilla SVGFEDistantLightElement documentation>
newtype SVGFEDistantLightElement = SVGFEDistantLightElement { SVGFEDistantLightElement -> JSVal
unSVGFEDistantLightElement :: JSVal }

instance PToJSVal SVGFEDistantLightElement where
  pToJSVal :: SVGFEDistantLightElement -> JSVal
pToJSVal = SVGFEDistantLightElement -> JSVal
unSVGFEDistantLightElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEDistantLightElement where
  pFromJSVal :: JSVal -> SVGFEDistantLightElement
pFromJSVal = JSVal -> SVGFEDistantLightElement
SVGFEDistantLightElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEDistantLightElement where
  toJSVal :: SVGFEDistantLightElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEDistantLightElement -> JSVal)
-> SVGFEDistantLightElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEDistantLightElement -> JSVal
unSVGFEDistantLightElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEDistantLightElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEDistantLightElement)
fromJSVal JSVal
v = (JSVal -> SVGFEDistantLightElement)
-> Maybe JSVal -> Maybe SVGFEDistantLightElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEDistantLightElement
SVGFEDistantLightElement (Maybe JSVal -> Maybe SVGFEDistantLightElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEDistantLightElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEDistantLightElement
fromJSValUnchecked = SVGFEDistantLightElement -> JSM SVGFEDistantLightElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEDistantLightElement -> JSM SVGFEDistantLightElement)
-> (JSVal -> SVGFEDistantLightElement)
-> JSVal
-> JSM SVGFEDistantLightElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEDistantLightElement
SVGFEDistantLightElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEDistantLightElement where
  makeObject :: SVGFEDistantLightElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEDistantLightElement -> JSVal)
-> SVGFEDistantLightElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEDistantLightElement -> JSVal
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 :: SVGFEDistantLightElement -> JSM GType
typeGType SVGFEDistantLightElement
_ = JSM GType
gTypeSVGFEDistantLightElement
  {-# INLINE typeGType #-}

noSVGFEDistantLightElement :: Maybe SVGFEDistantLightElement
noSVGFEDistantLightElement :: Maybe SVGFEDistantLightElement
noSVGFEDistantLightElement = Maybe SVGFEDistantLightElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEDistantLightElement #-}

gTypeSVGFEDistantLightElement :: JSM GType
gTypeSVGFEDistantLightElement :: JSM GType
gTypeSVGFEDistantLightElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEDistantLightElement"

-- | Functions for this inteface are in "JSDOM.SVGFEDropShadowElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEDropShadowElement Mozilla SVGFEDropShadowElement documentation>
newtype SVGFEDropShadowElement = SVGFEDropShadowElement { SVGFEDropShadowElement -> JSVal
unSVGFEDropShadowElement :: JSVal }

instance PToJSVal SVGFEDropShadowElement where
  pToJSVal :: SVGFEDropShadowElement -> JSVal
pToJSVal = SVGFEDropShadowElement -> JSVal
unSVGFEDropShadowElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEDropShadowElement where
  pFromJSVal :: JSVal -> SVGFEDropShadowElement
pFromJSVal = JSVal -> SVGFEDropShadowElement
SVGFEDropShadowElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEDropShadowElement where
  toJSVal :: SVGFEDropShadowElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEDropShadowElement -> JSVal)
-> SVGFEDropShadowElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEDropShadowElement -> JSVal
unSVGFEDropShadowElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEDropShadowElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEDropShadowElement)
fromJSVal JSVal
v = (JSVal -> SVGFEDropShadowElement)
-> Maybe JSVal -> Maybe SVGFEDropShadowElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEDropShadowElement
SVGFEDropShadowElement (Maybe JSVal -> Maybe SVGFEDropShadowElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEDropShadowElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEDropShadowElement
fromJSValUnchecked = SVGFEDropShadowElement -> JSM SVGFEDropShadowElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEDropShadowElement -> JSM SVGFEDropShadowElement)
-> (JSVal -> SVGFEDropShadowElement)
-> JSVal
-> JSM SVGFEDropShadowElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEDropShadowElement
SVGFEDropShadowElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEDropShadowElement where
  makeObject :: SVGFEDropShadowElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEDropShadowElement -> JSVal)
-> SVGFEDropShadowElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEDropShadowElement -> JSVal
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 :: SVGFEDropShadowElement -> JSM GType
typeGType SVGFEDropShadowElement
_ = JSM GType
gTypeSVGFEDropShadowElement
  {-# INLINE typeGType #-}

noSVGFEDropShadowElement :: Maybe SVGFEDropShadowElement
noSVGFEDropShadowElement :: Maybe SVGFEDropShadowElement
noSVGFEDropShadowElement = Maybe SVGFEDropShadowElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEDropShadowElement #-}

gTypeSVGFEDropShadowElement :: JSM GType
gTypeSVGFEDropShadowElement :: JSM GType
gTypeSVGFEDropShadowElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEDropShadowElement"

-- | Functions for this inteface are in "JSDOM.SVGFEFloodElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEFloodElement Mozilla SVGFEFloodElement documentation>
newtype SVGFEFloodElement = SVGFEFloodElement { SVGFEFloodElement -> JSVal
unSVGFEFloodElement :: JSVal }

instance PToJSVal SVGFEFloodElement where
  pToJSVal :: SVGFEFloodElement -> JSVal
pToJSVal = SVGFEFloodElement -> JSVal
unSVGFEFloodElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEFloodElement where
  pFromJSVal :: JSVal -> SVGFEFloodElement
pFromJSVal = JSVal -> SVGFEFloodElement
SVGFEFloodElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEFloodElement where
  toJSVal :: SVGFEFloodElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEFloodElement -> JSVal) -> SVGFEFloodElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEFloodElement -> JSVal
unSVGFEFloodElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEFloodElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEFloodElement)
fromJSVal JSVal
v = (JSVal -> SVGFEFloodElement)
-> Maybe JSVal -> Maybe SVGFEFloodElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEFloodElement
SVGFEFloodElement (Maybe JSVal -> Maybe SVGFEFloodElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEFloodElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEFloodElement
fromJSValUnchecked = SVGFEFloodElement -> JSM SVGFEFloodElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEFloodElement -> JSM SVGFEFloodElement)
-> (JSVal -> SVGFEFloodElement) -> JSVal -> JSM SVGFEFloodElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEFloodElement
SVGFEFloodElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEFloodElement where
  makeObject :: SVGFEFloodElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEFloodElement -> JSVal) -> SVGFEFloodElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEFloodElement -> JSVal
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 :: SVGFEFloodElement -> JSM GType
typeGType SVGFEFloodElement
_ = JSM GType
gTypeSVGFEFloodElement
  {-# INLINE typeGType #-}

noSVGFEFloodElement :: Maybe SVGFEFloodElement
noSVGFEFloodElement :: Maybe SVGFEFloodElement
noSVGFEFloodElement = Maybe SVGFEFloodElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEFloodElement #-}

gTypeSVGFEFloodElement :: JSM GType
gTypeSVGFEFloodElement :: JSM GType
gTypeSVGFEFloodElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEFloodElement"

-- | Functions for this inteface are in "JSDOM.SVGFEFuncAElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGComponentTransferFunctionElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEFuncAElement Mozilla SVGFEFuncAElement documentation>
newtype SVGFEFuncAElement = SVGFEFuncAElement { SVGFEFuncAElement -> JSVal
unSVGFEFuncAElement :: JSVal }

instance PToJSVal SVGFEFuncAElement where
  pToJSVal :: SVGFEFuncAElement -> JSVal
pToJSVal = SVGFEFuncAElement -> JSVal
unSVGFEFuncAElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEFuncAElement where
  pFromJSVal :: JSVal -> SVGFEFuncAElement
pFromJSVal = JSVal -> SVGFEFuncAElement
SVGFEFuncAElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEFuncAElement where
  toJSVal :: SVGFEFuncAElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEFuncAElement -> JSVal) -> SVGFEFuncAElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEFuncAElement -> JSVal
unSVGFEFuncAElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEFuncAElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEFuncAElement)
fromJSVal JSVal
v = (JSVal -> SVGFEFuncAElement)
-> Maybe JSVal -> Maybe SVGFEFuncAElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEFuncAElement
SVGFEFuncAElement (Maybe JSVal -> Maybe SVGFEFuncAElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEFuncAElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEFuncAElement
fromJSValUnchecked = SVGFEFuncAElement -> JSM SVGFEFuncAElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEFuncAElement -> JSM SVGFEFuncAElement)
-> (JSVal -> SVGFEFuncAElement) -> JSVal -> JSM SVGFEFuncAElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEFuncAElement
SVGFEFuncAElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEFuncAElement where
  makeObject :: SVGFEFuncAElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEFuncAElement -> JSVal) -> SVGFEFuncAElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEFuncAElement -> JSVal
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 :: SVGFEFuncAElement -> JSM GType
typeGType SVGFEFuncAElement
_ = JSM GType
gTypeSVGFEFuncAElement
  {-# INLINE typeGType #-}

noSVGFEFuncAElement :: Maybe SVGFEFuncAElement
noSVGFEFuncAElement :: Maybe SVGFEFuncAElement
noSVGFEFuncAElement = Maybe SVGFEFuncAElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEFuncAElement #-}

gTypeSVGFEFuncAElement :: JSM GType
gTypeSVGFEFuncAElement :: JSM GType
gTypeSVGFEFuncAElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEFuncAElement"

-- | Functions for this inteface are in "JSDOM.SVGFEFuncBElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGComponentTransferFunctionElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEFuncBElement Mozilla SVGFEFuncBElement documentation>
newtype SVGFEFuncBElement = SVGFEFuncBElement { SVGFEFuncBElement -> JSVal
unSVGFEFuncBElement :: JSVal }

instance PToJSVal SVGFEFuncBElement where
  pToJSVal :: SVGFEFuncBElement -> JSVal
pToJSVal = SVGFEFuncBElement -> JSVal
unSVGFEFuncBElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEFuncBElement where
  pFromJSVal :: JSVal -> SVGFEFuncBElement
pFromJSVal = JSVal -> SVGFEFuncBElement
SVGFEFuncBElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEFuncBElement where
  toJSVal :: SVGFEFuncBElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEFuncBElement -> JSVal) -> SVGFEFuncBElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEFuncBElement -> JSVal
unSVGFEFuncBElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEFuncBElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEFuncBElement)
fromJSVal JSVal
v = (JSVal -> SVGFEFuncBElement)
-> Maybe JSVal -> Maybe SVGFEFuncBElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEFuncBElement
SVGFEFuncBElement (Maybe JSVal -> Maybe SVGFEFuncBElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEFuncBElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEFuncBElement
fromJSValUnchecked = SVGFEFuncBElement -> JSM SVGFEFuncBElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEFuncBElement -> JSM SVGFEFuncBElement)
-> (JSVal -> SVGFEFuncBElement) -> JSVal -> JSM SVGFEFuncBElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEFuncBElement
SVGFEFuncBElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEFuncBElement where
  makeObject :: SVGFEFuncBElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEFuncBElement -> JSVal) -> SVGFEFuncBElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEFuncBElement -> JSVal
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 :: SVGFEFuncBElement -> JSM GType
typeGType SVGFEFuncBElement
_ = JSM GType
gTypeSVGFEFuncBElement
  {-# INLINE typeGType #-}

noSVGFEFuncBElement :: Maybe SVGFEFuncBElement
noSVGFEFuncBElement :: Maybe SVGFEFuncBElement
noSVGFEFuncBElement = Maybe SVGFEFuncBElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEFuncBElement #-}

gTypeSVGFEFuncBElement :: JSM GType
gTypeSVGFEFuncBElement :: JSM GType
gTypeSVGFEFuncBElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEFuncBElement"

-- | Functions for this inteface are in "JSDOM.SVGFEFuncGElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGComponentTransferFunctionElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEFuncGElement Mozilla SVGFEFuncGElement documentation>
newtype SVGFEFuncGElement = SVGFEFuncGElement { SVGFEFuncGElement -> JSVal
unSVGFEFuncGElement :: JSVal }

instance PToJSVal SVGFEFuncGElement where
  pToJSVal :: SVGFEFuncGElement -> JSVal
pToJSVal = SVGFEFuncGElement -> JSVal
unSVGFEFuncGElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEFuncGElement where
  pFromJSVal :: JSVal -> SVGFEFuncGElement
pFromJSVal = JSVal -> SVGFEFuncGElement
SVGFEFuncGElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEFuncGElement where
  toJSVal :: SVGFEFuncGElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEFuncGElement -> JSVal) -> SVGFEFuncGElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEFuncGElement -> JSVal
unSVGFEFuncGElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEFuncGElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEFuncGElement)
fromJSVal JSVal
v = (JSVal -> SVGFEFuncGElement)
-> Maybe JSVal -> Maybe SVGFEFuncGElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEFuncGElement
SVGFEFuncGElement (Maybe JSVal -> Maybe SVGFEFuncGElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEFuncGElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEFuncGElement
fromJSValUnchecked = SVGFEFuncGElement -> JSM SVGFEFuncGElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEFuncGElement -> JSM SVGFEFuncGElement)
-> (JSVal -> SVGFEFuncGElement) -> JSVal -> JSM SVGFEFuncGElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEFuncGElement
SVGFEFuncGElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEFuncGElement where
  makeObject :: SVGFEFuncGElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEFuncGElement -> JSVal) -> SVGFEFuncGElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEFuncGElement -> JSVal
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 :: SVGFEFuncGElement -> JSM GType
typeGType SVGFEFuncGElement
_ = JSM GType
gTypeSVGFEFuncGElement
  {-# INLINE typeGType #-}

noSVGFEFuncGElement :: Maybe SVGFEFuncGElement
noSVGFEFuncGElement :: Maybe SVGFEFuncGElement
noSVGFEFuncGElement = Maybe SVGFEFuncGElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEFuncGElement #-}

gTypeSVGFEFuncGElement :: JSM GType
gTypeSVGFEFuncGElement :: JSM GType
gTypeSVGFEFuncGElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEFuncGElement"

-- | Functions for this inteface are in "JSDOM.SVGFEFuncRElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGComponentTransferFunctionElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEFuncRElement Mozilla SVGFEFuncRElement documentation>
newtype SVGFEFuncRElement = SVGFEFuncRElement { SVGFEFuncRElement -> JSVal
unSVGFEFuncRElement :: JSVal }

instance PToJSVal SVGFEFuncRElement where
  pToJSVal :: SVGFEFuncRElement -> JSVal
pToJSVal = SVGFEFuncRElement -> JSVal
unSVGFEFuncRElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEFuncRElement where
  pFromJSVal :: JSVal -> SVGFEFuncRElement
pFromJSVal = JSVal -> SVGFEFuncRElement
SVGFEFuncRElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEFuncRElement where
  toJSVal :: SVGFEFuncRElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEFuncRElement -> JSVal) -> SVGFEFuncRElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEFuncRElement -> JSVal
unSVGFEFuncRElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEFuncRElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEFuncRElement)
fromJSVal JSVal
v = (JSVal -> SVGFEFuncRElement)
-> Maybe JSVal -> Maybe SVGFEFuncRElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEFuncRElement
SVGFEFuncRElement (Maybe JSVal -> Maybe SVGFEFuncRElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEFuncRElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEFuncRElement
fromJSValUnchecked = SVGFEFuncRElement -> JSM SVGFEFuncRElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEFuncRElement -> JSM SVGFEFuncRElement)
-> (JSVal -> SVGFEFuncRElement) -> JSVal -> JSM SVGFEFuncRElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEFuncRElement
SVGFEFuncRElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEFuncRElement where
  makeObject :: SVGFEFuncRElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEFuncRElement -> JSVal) -> SVGFEFuncRElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEFuncRElement -> JSVal
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 :: SVGFEFuncRElement -> JSM GType
typeGType SVGFEFuncRElement
_ = JSM GType
gTypeSVGFEFuncRElement
  {-# INLINE typeGType #-}

noSVGFEFuncRElement :: Maybe SVGFEFuncRElement
noSVGFEFuncRElement :: Maybe SVGFEFuncRElement
noSVGFEFuncRElement = Maybe SVGFEFuncRElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEFuncRElement #-}

gTypeSVGFEFuncRElement :: JSM GType
gTypeSVGFEFuncRElement :: JSM GType
gTypeSVGFEFuncRElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEFuncRElement"

-- | Functions for this inteface are in "JSDOM.SVGFEGaussianBlurElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEGaussianBlurElement Mozilla SVGFEGaussianBlurElement documentation>
newtype SVGFEGaussianBlurElement = SVGFEGaussianBlurElement { SVGFEGaussianBlurElement -> JSVal
unSVGFEGaussianBlurElement :: JSVal }

instance PToJSVal SVGFEGaussianBlurElement where
  pToJSVal :: SVGFEGaussianBlurElement -> JSVal
pToJSVal = SVGFEGaussianBlurElement -> JSVal
unSVGFEGaussianBlurElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEGaussianBlurElement where
  pFromJSVal :: JSVal -> SVGFEGaussianBlurElement
pFromJSVal = JSVal -> SVGFEGaussianBlurElement
SVGFEGaussianBlurElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEGaussianBlurElement where
  toJSVal :: SVGFEGaussianBlurElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEGaussianBlurElement -> JSVal)
-> SVGFEGaussianBlurElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEGaussianBlurElement -> JSVal
unSVGFEGaussianBlurElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEGaussianBlurElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEGaussianBlurElement)
fromJSVal JSVal
v = (JSVal -> SVGFEGaussianBlurElement)
-> Maybe JSVal -> Maybe SVGFEGaussianBlurElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEGaussianBlurElement
SVGFEGaussianBlurElement (Maybe JSVal -> Maybe SVGFEGaussianBlurElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEGaussianBlurElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEGaussianBlurElement
fromJSValUnchecked = SVGFEGaussianBlurElement -> JSM SVGFEGaussianBlurElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEGaussianBlurElement -> JSM SVGFEGaussianBlurElement)
-> (JSVal -> SVGFEGaussianBlurElement)
-> JSVal
-> JSM SVGFEGaussianBlurElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEGaussianBlurElement
SVGFEGaussianBlurElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEGaussianBlurElement where
  makeObject :: SVGFEGaussianBlurElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEGaussianBlurElement -> JSVal)
-> SVGFEGaussianBlurElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEGaussianBlurElement -> JSVal
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 :: SVGFEGaussianBlurElement -> JSM GType
typeGType SVGFEGaussianBlurElement
_ = JSM GType
gTypeSVGFEGaussianBlurElement
  {-# INLINE typeGType #-}

noSVGFEGaussianBlurElement :: Maybe SVGFEGaussianBlurElement
noSVGFEGaussianBlurElement :: Maybe SVGFEGaussianBlurElement
noSVGFEGaussianBlurElement = Maybe SVGFEGaussianBlurElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEGaussianBlurElement #-}

gTypeSVGFEGaussianBlurElement :: JSM GType
gTypeSVGFEGaussianBlurElement :: JSM GType
gTypeSVGFEGaussianBlurElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEGaussianBlurElement"

-- | Functions for this inteface are in "JSDOM.SVGFEImageElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEImageElement Mozilla SVGFEImageElement documentation>
newtype SVGFEImageElement = SVGFEImageElement { SVGFEImageElement -> JSVal
unSVGFEImageElement :: JSVal }

instance PToJSVal SVGFEImageElement where
  pToJSVal :: SVGFEImageElement -> JSVal
pToJSVal = SVGFEImageElement -> JSVal
unSVGFEImageElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEImageElement where
  pFromJSVal :: JSVal -> SVGFEImageElement
pFromJSVal = JSVal -> SVGFEImageElement
SVGFEImageElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEImageElement where
  toJSVal :: SVGFEImageElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEImageElement -> JSVal) -> SVGFEImageElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEImageElement -> JSVal
unSVGFEImageElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEImageElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEImageElement)
fromJSVal JSVal
v = (JSVal -> SVGFEImageElement)
-> Maybe JSVal -> Maybe SVGFEImageElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEImageElement
SVGFEImageElement (Maybe JSVal -> Maybe SVGFEImageElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEImageElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEImageElement
fromJSValUnchecked = SVGFEImageElement -> JSM SVGFEImageElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEImageElement -> JSM SVGFEImageElement)
-> (JSVal -> SVGFEImageElement) -> JSVal -> JSM SVGFEImageElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEImageElement
SVGFEImageElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEImageElement where
  makeObject :: SVGFEImageElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEImageElement -> JSVal) -> SVGFEImageElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEImageElement -> JSVal
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 :: SVGFEImageElement -> JSM GType
typeGType SVGFEImageElement
_ = JSM GType
gTypeSVGFEImageElement
  {-# INLINE typeGType #-}

noSVGFEImageElement :: Maybe SVGFEImageElement
noSVGFEImageElement :: Maybe SVGFEImageElement
noSVGFEImageElement = Maybe SVGFEImageElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEImageElement #-}

gTypeSVGFEImageElement :: JSM GType
gTypeSVGFEImageElement :: JSM GType
gTypeSVGFEImageElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEImageElement"

-- | Functions for this inteface are in "JSDOM.SVGFEMergeElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEMergeElement Mozilla SVGFEMergeElement documentation>
newtype SVGFEMergeElement = SVGFEMergeElement { SVGFEMergeElement -> JSVal
unSVGFEMergeElement :: JSVal }

instance PToJSVal SVGFEMergeElement where
  pToJSVal :: SVGFEMergeElement -> JSVal
pToJSVal = SVGFEMergeElement -> JSVal
unSVGFEMergeElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEMergeElement where
  pFromJSVal :: JSVal -> SVGFEMergeElement
pFromJSVal = JSVal -> SVGFEMergeElement
SVGFEMergeElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEMergeElement where
  toJSVal :: SVGFEMergeElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEMergeElement -> JSVal) -> SVGFEMergeElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEMergeElement -> JSVal
unSVGFEMergeElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEMergeElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEMergeElement)
fromJSVal JSVal
v = (JSVal -> SVGFEMergeElement)
-> Maybe JSVal -> Maybe SVGFEMergeElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEMergeElement
SVGFEMergeElement (Maybe JSVal -> Maybe SVGFEMergeElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEMergeElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEMergeElement
fromJSValUnchecked = SVGFEMergeElement -> JSM SVGFEMergeElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEMergeElement -> JSM SVGFEMergeElement)
-> (JSVal -> SVGFEMergeElement) -> JSVal -> JSM SVGFEMergeElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEMergeElement
SVGFEMergeElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEMergeElement where
  makeObject :: SVGFEMergeElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEMergeElement -> JSVal) -> SVGFEMergeElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEMergeElement -> JSVal
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 :: SVGFEMergeElement -> JSM GType
typeGType SVGFEMergeElement
_ = JSM GType
gTypeSVGFEMergeElement
  {-# INLINE typeGType #-}

noSVGFEMergeElement :: Maybe SVGFEMergeElement
noSVGFEMergeElement :: Maybe SVGFEMergeElement
noSVGFEMergeElement = Maybe SVGFEMergeElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEMergeElement #-}

gTypeSVGFEMergeElement :: JSM GType
gTypeSVGFEMergeElement :: JSM GType
gTypeSVGFEMergeElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEMergeElement"

-- | Functions for this inteface are in "JSDOM.SVGFEMergeNodeElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEMergeNodeElement Mozilla SVGFEMergeNodeElement documentation>
newtype SVGFEMergeNodeElement = SVGFEMergeNodeElement { SVGFEMergeNodeElement -> JSVal
unSVGFEMergeNodeElement :: JSVal }

instance PToJSVal SVGFEMergeNodeElement where
  pToJSVal :: SVGFEMergeNodeElement -> JSVal
pToJSVal = SVGFEMergeNodeElement -> JSVal
unSVGFEMergeNodeElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEMergeNodeElement where
  pFromJSVal :: JSVal -> SVGFEMergeNodeElement
pFromJSVal = JSVal -> SVGFEMergeNodeElement
SVGFEMergeNodeElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEMergeNodeElement where
  toJSVal :: SVGFEMergeNodeElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEMergeNodeElement -> JSVal)
-> SVGFEMergeNodeElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEMergeNodeElement -> JSVal
unSVGFEMergeNodeElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEMergeNodeElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEMergeNodeElement)
fromJSVal JSVal
v = (JSVal -> SVGFEMergeNodeElement)
-> Maybe JSVal -> Maybe SVGFEMergeNodeElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEMergeNodeElement
SVGFEMergeNodeElement (Maybe JSVal -> Maybe SVGFEMergeNodeElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEMergeNodeElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEMergeNodeElement
fromJSValUnchecked = SVGFEMergeNodeElement -> JSM SVGFEMergeNodeElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEMergeNodeElement -> JSM SVGFEMergeNodeElement)
-> (JSVal -> SVGFEMergeNodeElement)
-> JSVal
-> JSM SVGFEMergeNodeElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEMergeNodeElement
SVGFEMergeNodeElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEMergeNodeElement where
  makeObject :: SVGFEMergeNodeElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEMergeNodeElement -> JSVal)
-> SVGFEMergeNodeElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEMergeNodeElement -> JSVal
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 :: SVGFEMergeNodeElement -> JSM GType
typeGType SVGFEMergeNodeElement
_ = JSM GType
gTypeSVGFEMergeNodeElement
  {-# INLINE typeGType #-}

noSVGFEMergeNodeElement :: Maybe SVGFEMergeNodeElement
noSVGFEMergeNodeElement :: Maybe SVGFEMergeNodeElement
noSVGFEMergeNodeElement = Maybe SVGFEMergeNodeElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEMergeNodeElement #-}

gTypeSVGFEMergeNodeElement :: JSM GType
gTypeSVGFEMergeNodeElement :: JSM GType
gTypeSVGFEMergeNodeElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEMergeNodeElement"

-- | Functions for this inteface are in "JSDOM.SVGFEMorphologyElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEMorphologyElement Mozilla SVGFEMorphologyElement documentation>
newtype SVGFEMorphologyElement = SVGFEMorphologyElement { SVGFEMorphologyElement -> JSVal
unSVGFEMorphologyElement :: JSVal }

instance PToJSVal SVGFEMorphologyElement where
  pToJSVal :: SVGFEMorphologyElement -> JSVal
pToJSVal = SVGFEMorphologyElement -> JSVal
unSVGFEMorphologyElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEMorphologyElement where
  pFromJSVal :: JSVal -> SVGFEMorphologyElement
pFromJSVal = JSVal -> SVGFEMorphologyElement
SVGFEMorphologyElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEMorphologyElement where
  toJSVal :: SVGFEMorphologyElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEMorphologyElement -> JSVal)
-> SVGFEMorphologyElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEMorphologyElement -> JSVal
unSVGFEMorphologyElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEMorphologyElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEMorphologyElement)
fromJSVal JSVal
v = (JSVal -> SVGFEMorphologyElement)
-> Maybe JSVal -> Maybe SVGFEMorphologyElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEMorphologyElement
SVGFEMorphologyElement (Maybe JSVal -> Maybe SVGFEMorphologyElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEMorphologyElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEMorphologyElement
fromJSValUnchecked = SVGFEMorphologyElement -> JSM SVGFEMorphologyElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEMorphologyElement -> JSM SVGFEMorphologyElement)
-> (JSVal -> SVGFEMorphologyElement)
-> JSVal
-> JSM SVGFEMorphologyElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEMorphologyElement
SVGFEMorphologyElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEMorphologyElement where
  makeObject :: SVGFEMorphologyElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEMorphologyElement -> JSVal)
-> SVGFEMorphologyElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEMorphologyElement -> JSVal
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 :: SVGFEMorphologyElement -> JSM GType
typeGType SVGFEMorphologyElement
_ = JSM GType
gTypeSVGFEMorphologyElement
  {-# INLINE typeGType #-}

noSVGFEMorphologyElement :: Maybe SVGFEMorphologyElement
noSVGFEMorphologyElement :: Maybe SVGFEMorphologyElement
noSVGFEMorphologyElement = Maybe SVGFEMorphologyElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEMorphologyElement #-}

gTypeSVGFEMorphologyElement :: JSM GType
gTypeSVGFEMorphologyElement :: JSM GType
gTypeSVGFEMorphologyElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEMorphologyElement"

-- | Functions for this inteface are in "JSDOM.SVGFEOffsetElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEOffsetElement Mozilla SVGFEOffsetElement documentation>
newtype SVGFEOffsetElement = SVGFEOffsetElement { SVGFEOffsetElement -> JSVal
unSVGFEOffsetElement :: JSVal }

instance PToJSVal SVGFEOffsetElement where
  pToJSVal :: SVGFEOffsetElement -> JSVal
pToJSVal = SVGFEOffsetElement -> JSVal
unSVGFEOffsetElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEOffsetElement where
  pFromJSVal :: JSVal -> SVGFEOffsetElement
pFromJSVal = JSVal -> SVGFEOffsetElement
SVGFEOffsetElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEOffsetElement where
  toJSVal :: SVGFEOffsetElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEOffsetElement -> JSVal) -> SVGFEOffsetElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEOffsetElement -> JSVal
unSVGFEOffsetElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEOffsetElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEOffsetElement)
fromJSVal JSVal
v = (JSVal -> SVGFEOffsetElement)
-> Maybe JSVal -> Maybe SVGFEOffsetElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEOffsetElement
SVGFEOffsetElement (Maybe JSVal -> Maybe SVGFEOffsetElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEOffsetElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEOffsetElement
fromJSValUnchecked = SVGFEOffsetElement -> JSM SVGFEOffsetElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEOffsetElement -> JSM SVGFEOffsetElement)
-> (JSVal -> SVGFEOffsetElement) -> JSVal -> JSM SVGFEOffsetElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEOffsetElement
SVGFEOffsetElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEOffsetElement where
  makeObject :: SVGFEOffsetElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEOffsetElement -> JSVal)
-> SVGFEOffsetElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEOffsetElement -> JSVal
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 :: SVGFEOffsetElement -> JSM GType
typeGType SVGFEOffsetElement
_ = JSM GType
gTypeSVGFEOffsetElement
  {-# INLINE typeGType #-}

noSVGFEOffsetElement :: Maybe SVGFEOffsetElement
noSVGFEOffsetElement :: Maybe SVGFEOffsetElement
noSVGFEOffsetElement = Maybe SVGFEOffsetElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEOffsetElement #-}

gTypeSVGFEOffsetElement :: JSM GType
gTypeSVGFEOffsetElement :: JSM GType
gTypeSVGFEOffsetElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEOffsetElement"

-- | Functions for this inteface are in "JSDOM.SVGFEPointLightElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFEPointLightElement Mozilla SVGFEPointLightElement documentation>
newtype SVGFEPointLightElement = SVGFEPointLightElement { SVGFEPointLightElement -> JSVal
unSVGFEPointLightElement :: JSVal }

instance PToJSVal SVGFEPointLightElement where
  pToJSVal :: SVGFEPointLightElement -> JSVal
pToJSVal = SVGFEPointLightElement -> JSVal
unSVGFEPointLightElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFEPointLightElement where
  pFromJSVal :: JSVal -> SVGFEPointLightElement
pFromJSVal = JSVal -> SVGFEPointLightElement
SVGFEPointLightElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFEPointLightElement where
  toJSVal :: SVGFEPointLightElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFEPointLightElement -> JSVal)
-> SVGFEPointLightElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEPointLightElement -> JSVal
unSVGFEPointLightElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFEPointLightElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFEPointLightElement)
fromJSVal JSVal
v = (JSVal -> SVGFEPointLightElement)
-> Maybe JSVal -> Maybe SVGFEPointLightElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFEPointLightElement
SVGFEPointLightElement (Maybe JSVal -> Maybe SVGFEPointLightElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFEPointLightElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFEPointLightElement
fromJSValUnchecked = SVGFEPointLightElement -> JSM SVGFEPointLightElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFEPointLightElement -> JSM SVGFEPointLightElement)
-> (JSVal -> SVGFEPointLightElement)
-> JSVal
-> JSM SVGFEPointLightElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFEPointLightElement
SVGFEPointLightElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFEPointLightElement where
  makeObject :: SVGFEPointLightElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFEPointLightElement -> JSVal)
-> SVGFEPointLightElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFEPointLightElement -> JSVal
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 :: SVGFEPointLightElement -> JSM GType
typeGType SVGFEPointLightElement
_ = JSM GType
gTypeSVGFEPointLightElement
  {-# INLINE typeGType #-}

noSVGFEPointLightElement :: Maybe SVGFEPointLightElement
noSVGFEPointLightElement :: Maybe SVGFEPointLightElement
noSVGFEPointLightElement = Maybe SVGFEPointLightElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFEPointLightElement #-}

gTypeSVGFEPointLightElement :: JSM GType
gTypeSVGFEPointLightElement :: JSM GType
gTypeSVGFEPointLightElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFEPointLightElement"

-- | Functions for this inteface are in "JSDOM.SVGFESpecularLightingElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFESpecularLightingElement Mozilla SVGFESpecularLightingElement documentation>
newtype SVGFESpecularLightingElement = SVGFESpecularLightingElement { SVGFESpecularLightingElement -> JSVal
unSVGFESpecularLightingElement :: JSVal }

instance PToJSVal SVGFESpecularLightingElement where
  pToJSVal :: SVGFESpecularLightingElement -> JSVal
pToJSVal = SVGFESpecularLightingElement -> JSVal
unSVGFESpecularLightingElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFESpecularLightingElement where
  pFromJSVal :: JSVal -> SVGFESpecularLightingElement
pFromJSVal = JSVal -> SVGFESpecularLightingElement
SVGFESpecularLightingElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFESpecularLightingElement where
  toJSVal :: SVGFESpecularLightingElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFESpecularLightingElement -> JSVal)
-> SVGFESpecularLightingElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFESpecularLightingElement -> JSVal
unSVGFESpecularLightingElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFESpecularLightingElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFESpecularLightingElement)
fromJSVal JSVal
v = (JSVal -> SVGFESpecularLightingElement)
-> Maybe JSVal -> Maybe SVGFESpecularLightingElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFESpecularLightingElement
SVGFESpecularLightingElement (Maybe JSVal -> Maybe SVGFESpecularLightingElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFESpecularLightingElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFESpecularLightingElement
fromJSValUnchecked = SVGFESpecularLightingElement -> JSM SVGFESpecularLightingElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFESpecularLightingElement -> JSM SVGFESpecularLightingElement)
-> (JSVal -> SVGFESpecularLightingElement)
-> JSVal
-> JSM SVGFESpecularLightingElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFESpecularLightingElement
SVGFESpecularLightingElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFESpecularLightingElement where
  makeObject :: SVGFESpecularLightingElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFESpecularLightingElement -> JSVal)
-> SVGFESpecularLightingElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFESpecularLightingElement -> JSVal
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 :: SVGFESpecularLightingElement -> JSM GType
typeGType SVGFESpecularLightingElement
_ = JSM GType
gTypeSVGFESpecularLightingElement
  {-# INLINE typeGType #-}

noSVGFESpecularLightingElement :: Maybe SVGFESpecularLightingElement
noSVGFESpecularLightingElement :: Maybe SVGFESpecularLightingElement
noSVGFESpecularLightingElement = Maybe SVGFESpecularLightingElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFESpecularLightingElement #-}

gTypeSVGFESpecularLightingElement :: JSM GType
gTypeSVGFESpecularLightingElement :: JSM GType
gTypeSVGFESpecularLightingElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFESpecularLightingElement"

-- | Functions for this inteface are in "JSDOM.SVGFESpotLightElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFESpotLightElement Mozilla SVGFESpotLightElement documentation>
newtype SVGFESpotLightElement = SVGFESpotLightElement { SVGFESpotLightElement -> JSVal
unSVGFESpotLightElement :: JSVal }

instance PToJSVal SVGFESpotLightElement where
  pToJSVal :: SVGFESpotLightElement -> JSVal
pToJSVal = SVGFESpotLightElement -> JSVal
unSVGFESpotLightElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFESpotLightElement where
  pFromJSVal :: JSVal -> SVGFESpotLightElement
pFromJSVal = JSVal -> SVGFESpotLightElement
SVGFESpotLightElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFESpotLightElement where
  toJSVal :: SVGFESpotLightElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFESpotLightElement -> JSVal)
-> SVGFESpotLightElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFESpotLightElement -> JSVal
unSVGFESpotLightElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFESpotLightElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFESpotLightElement)
fromJSVal JSVal
v = (JSVal -> SVGFESpotLightElement)
-> Maybe JSVal -> Maybe SVGFESpotLightElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFESpotLightElement
SVGFESpotLightElement (Maybe JSVal -> Maybe SVGFESpotLightElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFESpotLightElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFESpotLightElement
fromJSValUnchecked = SVGFESpotLightElement -> JSM SVGFESpotLightElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFESpotLightElement -> JSM SVGFESpotLightElement)
-> (JSVal -> SVGFESpotLightElement)
-> JSVal
-> JSM SVGFESpotLightElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFESpotLightElement
SVGFESpotLightElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFESpotLightElement where
  makeObject :: SVGFESpotLightElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFESpotLightElement -> JSVal)
-> SVGFESpotLightElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFESpotLightElement -> JSVal
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 :: SVGFESpotLightElement -> JSM GType
typeGType SVGFESpotLightElement
_ = JSM GType
gTypeSVGFESpotLightElement
  {-# INLINE typeGType #-}

noSVGFESpotLightElement :: Maybe SVGFESpotLightElement
noSVGFESpotLightElement :: Maybe SVGFESpotLightElement
noSVGFESpotLightElement = Maybe SVGFESpotLightElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFESpotLightElement #-}

gTypeSVGFESpotLightElement :: JSM GType
gTypeSVGFESpotLightElement :: JSM GType
gTypeSVGFESpotLightElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFESpotLightElement"

-- | Functions for this inteface are in "JSDOM.SVGFETileElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFETileElement Mozilla SVGFETileElement documentation>
newtype SVGFETileElement = SVGFETileElement { SVGFETileElement -> JSVal
unSVGFETileElement :: JSVal }

instance PToJSVal SVGFETileElement where
  pToJSVal :: SVGFETileElement -> JSVal
pToJSVal = SVGFETileElement -> JSVal
unSVGFETileElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFETileElement where
  pFromJSVal :: JSVal -> SVGFETileElement
pFromJSVal = JSVal -> SVGFETileElement
SVGFETileElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFETileElement where
  toJSVal :: SVGFETileElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFETileElement -> JSVal) -> SVGFETileElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFETileElement -> JSVal
unSVGFETileElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFETileElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFETileElement)
fromJSVal JSVal
v = (JSVal -> SVGFETileElement)
-> Maybe JSVal -> Maybe SVGFETileElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFETileElement
SVGFETileElement (Maybe JSVal -> Maybe SVGFETileElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFETileElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFETileElement
fromJSValUnchecked = SVGFETileElement -> JSM SVGFETileElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFETileElement -> JSM SVGFETileElement)
-> (JSVal -> SVGFETileElement) -> JSVal -> JSM SVGFETileElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFETileElement
SVGFETileElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFETileElement where
  makeObject :: SVGFETileElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFETileElement -> JSVal) -> SVGFETileElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFETileElement -> JSVal
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 :: SVGFETileElement -> JSM GType
typeGType SVGFETileElement
_ = JSM GType
gTypeSVGFETileElement
  {-# INLINE typeGType #-}

noSVGFETileElement :: Maybe SVGFETileElement
noSVGFETileElement :: Maybe SVGFETileElement
noSVGFETileElement = Maybe SVGFETileElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFETileElement #-}

gTypeSVGFETileElement :: JSM GType
gTypeSVGFETileElement :: JSM GType
gTypeSVGFETileElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFETileElement"

-- | Functions for this inteface are in "JSDOM.SVGFETurbulenceElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFilterPrimitiveStandardAttributes"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFETurbulenceElement Mozilla SVGFETurbulenceElement documentation>
newtype SVGFETurbulenceElement = SVGFETurbulenceElement { SVGFETurbulenceElement -> JSVal
unSVGFETurbulenceElement :: JSVal }

instance PToJSVal SVGFETurbulenceElement where
  pToJSVal :: SVGFETurbulenceElement -> JSVal
pToJSVal = SVGFETurbulenceElement -> JSVal
unSVGFETurbulenceElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFETurbulenceElement where
  pFromJSVal :: JSVal -> SVGFETurbulenceElement
pFromJSVal = JSVal -> SVGFETurbulenceElement
SVGFETurbulenceElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFETurbulenceElement where
  toJSVal :: SVGFETurbulenceElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFETurbulenceElement -> JSVal)
-> SVGFETurbulenceElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFETurbulenceElement -> JSVal
unSVGFETurbulenceElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFETurbulenceElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFETurbulenceElement)
fromJSVal JSVal
v = (JSVal -> SVGFETurbulenceElement)
-> Maybe JSVal -> Maybe SVGFETurbulenceElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFETurbulenceElement
SVGFETurbulenceElement (Maybe JSVal -> Maybe SVGFETurbulenceElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFETurbulenceElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFETurbulenceElement
fromJSValUnchecked = SVGFETurbulenceElement -> JSM SVGFETurbulenceElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFETurbulenceElement -> JSM SVGFETurbulenceElement)
-> (JSVal -> SVGFETurbulenceElement)
-> JSVal
-> JSM SVGFETurbulenceElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFETurbulenceElement
SVGFETurbulenceElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFETurbulenceElement where
  makeObject :: SVGFETurbulenceElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFETurbulenceElement -> JSVal)
-> SVGFETurbulenceElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFETurbulenceElement -> JSVal
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 :: SVGFETurbulenceElement -> JSM GType
typeGType SVGFETurbulenceElement
_ = JSM GType
gTypeSVGFETurbulenceElement
  {-# INLINE typeGType #-}

noSVGFETurbulenceElement :: Maybe SVGFETurbulenceElement
noSVGFETurbulenceElement :: Maybe SVGFETurbulenceElement
noSVGFETurbulenceElement = Maybe SVGFETurbulenceElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFETurbulenceElement #-}

gTypeSVGFETurbulenceElement :: JSM GType
gTypeSVGFETurbulenceElement :: JSM GType
gTypeSVGFETurbulenceElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFETurbulenceElement"

-- | Functions for this inteface are in "JSDOM.SVGFilterElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFilterElement Mozilla SVGFilterElement documentation>
newtype SVGFilterElement = SVGFilterElement { SVGFilterElement -> JSVal
unSVGFilterElement :: JSVal }

instance PToJSVal SVGFilterElement where
  pToJSVal :: SVGFilterElement -> JSVal
pToJSVal = SVGFilterElement -> JSVal
unSVGFilterElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFilterElement where
  pFromJSVal :: JSVal -> SVGFilterElement
pFromJSVal = JSVal -> SVGFilterElement
SVGFilterElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFilterElement where
  toJSVal :: SVGFilterElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFilterElement -> JSVal) -> SVGFilterElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFilterElement -> JSVal
unSVGFilterElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFilterElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFilterElement)
fromJSVal JSVal
v = (JSVal -> SVGFilterElement)
-> Maybe JSVal -> Maybe SVGFilterElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFilterElement
SVGFilterElement (Maybe JSVal -> Maybe SVGFilterElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFilterElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFilterElement
fromJSValUnchecked = SVGFilterElement -> JSM SVGFilterElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFilterElement -> JSM SVGFilterElement)
-> (JSVal -> SVGFilterElement) -> JSVal -> JSM SVGFilterElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFilterElement
SVGFilterElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFilterElement where
  makeObject :: SVGFilterElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFilterElement -> JSVal) -> SVGFilterElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFilterElement -> JSVal
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 :: SVGFilterElement -> JSM GType
typeGType SVGFilterElement
_ = JSM GType
gTypeSVGFilterElement
  {-# INLINE typeGType #-}

noSVGFilterElement :: Maybe SVGFilterElement
noSVGFilterElement :: Maybe SVGFilterElement
noSVGFilterElement = Maybe SVGFilterElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFilterElement #-}

gTypeSVGFilterElement :: JSM GType
gTypeSVGFilterElement :: JSM GType
gTypeSVGFilterElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFilterElement"

-- | Functions for this inteface are in "JSDOM.SVGFilterPrimitiveStandardAttributes".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFilterPrimitiveStandardAttributes Mozilla SVGFilterPrimitiveStandardAttributes documentation>
newtype SVGFilterPrimitiveStandardAttributes = SVGFilterPrimitiveStandardAttributes { SVGFilterPrimitiveStandardAttributes -> JSVal
unSVGFilterPrimitiveStandardAttributes :: JSVal }

instance PToJSVal SVGFilterPrimitiveStandardAttributes where
  pToJSVal :: SVGFilterPrimitiveStandardAttributes -> JSVal
pToJSVal = SVGFilterPrimitiveStandardAttributes -> JSVal
unSVGFilterPrimitiveStandardAttributes
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFilterPrimitiveStandardAttributes where
  pFromJSVal :: JSVal -> SVGFilterPrimitiveStandardAttributes
pFromJSVal = JSVal -> SVGFilterPrimitiveStandardAttributes
SVGFilterPrimitiveStandardAttributes
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFilterPrimitiveStandardAttributes where
  toJSVal :: SVGFilterPrimitiveStandardAttributes -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFilterPrimitiveStandardAttributes -> JSVal)
-> SVGFilterPrimitiveStandardAttributes
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFilterPrimitiveStandardAttributes -> JSVal
unSVGFilterPrimitiveStandardAttributes
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFilterPrimitiveStandardAttributes where
  fromJSVal :: JSVal -> JSM (Maybe SVGFilterPrimitiveStandardAttributes)
fromJSVal JSVal
v = (JSVal -> SVGFilterPrimitiveStandardAttributes)
-> Maybe JSVal -> Maybe SVGFilterPrimitiveStandardAttributes
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFilterPrimitiveStandardAttributes
SVGFilterPrimitiveStandardAttributes (Maybe JSVal -> Maybe SVGFilterPrimitiveStandardAttributes)
-> JSM (Maybe JSVal)
-> JSM (Maybe SVGFilterPrimitiveStandardAttributes)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFilterPrimitiveStandardAttributes
fromJSValUnchecked = SVGFilterPrimitiveStandardAttributes
-> JSM SVGFilterPrimitiveStandardAttributes
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFilterPrimitiveStandardAttributes
 -> JSM SVGFilterPrimitiveStandardAttributes)
-> (JSVal -> SVGFilterPrimitiveStandardAttributes)
-> JSVal
-> JSM SVGFilterPrimitiveStandardAttributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFilterPrimitiveStandardAttributes
SVGFilterPrimitiveStandardAttributes
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFilterPrimitiveStandardAttributes where
  makeObject :: SVGFilterPrimitiveStandardAttributes -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFilterPrimitiveStandardAttributes -> JSVal)
-> SVGFilterPrimitiveStandardAttributes
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFilterPrimitiveStandardAttributes -> JSVal
unSVGFilterPrimitiveStandardAttributes

class (IsGObject o) => IsSVGFilterPrimitiveStandardAttributes o
toSVGFilterPrimitiveStandardAttributes :: IsSVGFilterPrimitiveStandardAttributes o => o -> SVGFilterPrimitiveStandardAttributes
toSVGFilterPrimitiveStandardAttributes :: forall o.
IsSVGFilterPrimitiveStandardAttributes o =>
o -> SVGFilterPrimitiveStandardAttributes
toSVGFilterPrimitiveStandardAttributes = JSVal -> SVGFilterPrimitiveStandardAttributes
SVGFilterPrimitiveStandardAttributes (JSVal -> SVGFilterPrimitiveStandardAttributes)
-> (o -> JSVal) -> o -> SVGFilterPrimitiveStandardAttributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsSVGFilterPrimitiveStandardAttributes SVGFilterPrimitiveStandardAttributes
instance IsGObject SVGFilterPrimitiveStandardAttributes where
  typeGType :: SVGFilterPrimitiveStandardAttributes -> JSM GType
typeGType SVGFilterPrimitiveStandardAttributes
_ = JSM GType
gTypeSVGFilterPrimitiveStandardAttributes
  {-# INLINE typeGType #-}

noSVGFilterPrimitiveStandardAttributes :: Maybe SVGFilterPrimitiveStandardAttributes
noSVGFilterPrimitiveStandardAttributes :: Maybe SVGFilterPrimitiveStandardAttributes
noSVGFilterPrimitiveStandardAttributes = Maybe SVGFilterPrimitiveStandardAttributes
forall a. Maybe a
Nothing
{-# INLINE noSVGFilterPrimitiveStandardAttributes #-}

gTypeSVGFilterPrimitiveStandardAttributes :: JSM GType
gTypeSVGFilterPrimitiveStandardAttributes :: JSM GType
gTypeSVGFilterPrimitiveStandardAttributes = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFilterPrimitiveStandardAttributes"

-- | Functions for this inteface are in "JSDOM.SVGFitToViewBox".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFitToViewBox Mozilla SVGFitToViewBox documentation>
newtype SVGFitToViewBox = SVGFitToViewBox { SVGFitToViewBox -> JSVal
unSVGFitToViewBox :: JSVal }

instance PToJSVal SVGFitToViewBox where
  pToJSVal :: SVGFitToViewBox -> JSVal
pToJSVal = SVGFitToViewBox -> JSVal
unSVGFitToViewBox
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFitToViewBox where
  pFromJSVal :: JSVal -> SVGFitToViewBox
pFromJSVal = JSVal -> SVGFitToViewBox
SVGFitToViewBox
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFitToViewBox where
  toJSVal :: SVGFitToViewBox -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFitToViewBox -> JSVal) -> SVGFitToViewBox -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFitToViewBox -> JSVal
unSVGFitToViewBox
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFitToViewBox where
  fromJSVal :: JSVal -> JSM (Maybe SVGFitToViewBox)
fromJSVal JSVal
v = (JSVal -> SVGFitToViewBox) -> Maybe JSVal -> Maybe SVGFitToViewBox
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFitToViewBox
SVGFitToViewBox (Maybe JSVal -> Maybe SVGFitToViewBox)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFitToViewBox)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFitToViewBox
fromJSValUnchecked = SVGFitToViewBox -> JSM SVGFitToViewBox
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFitToViewBox -> JSM SVGFitToViewBox)
-> (JSVal -> SVGFitToViewBox) -> JSVal -> JSM SVGFitToViewBox
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFitToViewBox
SVGFitToViewBox
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFitToViewBox where
  makeObject :: SVGFitToViewBox -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFitToViewBox -> JSVal) -> SVGFitToViewBox -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFitToViewBox -> JSVal
unSVGFitToViewBox

class (IsGObject o) => IsSVGFitToViewBox o
toSVGFitToViewBox :: IsSVGFitToViewBox o => o -> SVGFitToViewBox
toSVGFitToViewBox :: forall o. IsSVGFitToViewBox o => o -> SVGFitToViewBox
toSVGFitToViewBox = JSVal -> SVGFitToViewBox
SVGFitToViewBox (JSVal -> SVGFitToViewBox) -> (o -> JSVal) -> o -> SVGFitToViewBox
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsSVGFitToViewBox SVGFitToViewBox
instance IsGObject SVGFitToViewBox where
  typeGType :: SVGFitToViewBox -> JSM GType
typeGType SVGFitToViewBox
_ = JSM GType
gTypeSVGFitToViewBox
  {-# INLINE typeGType #-}

noSVGFitToViewBox :: Maybe SVGFitToViewBox
noSVGFitToViewBox :: Maybe SVGFitToViewBox
noSVGFitToViewBox = Maybe SVGFitToViewBox
forall a. Maybe a
Nothing
{-# INLINE noSVGFitToViewBox #-}

gTypeSVGFitToViewBox :: JSM GType
gTypeSVGFitToViewBox :: JSM GType
gTypeSVGFitToViewBox = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFitToViewBox"

-- | Functions for this inteface are in "JSDOM.SVGFontElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFontElement Mozilla SVGFontElement documentation>
newtype SVGFontElement = SVGFontElement { SVGFontElement -> JSVal
unSVGFontElement :: JSVal }

instance PToJSVal SVGFontElement where
  pToJSVal :: SVGFontElement -> JSVal
pToJSVal = SVGFontElement -> JSVal
unSVGFontElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFontElement where
  pFromJSVal :: JSVal -> SVGFontElement
pFromJSVal = JSVal -> SVGFontElement
SVGFontElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFontElement where
  toJSVal :: SVGFontElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFontElement -> JSVal) -> SVGFontElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontElement -> JSVal
unSVGFontElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFontElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFontElement)
fromJSVal JSVal
v = (JSVal -> SVGFontElement) -> Maybe JSVal -> Maybe SVGFontElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFontElement
SVGFontElement (Maybe JSVal -> Maybe SVGFontElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFontElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFontElement
fromJSValUnchecked = SVGFontElement -> JSM SVGFontElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFontElement -> JSM SVGFontElement)
-> (JSVal -> SVGFontElement) -> JSVal -> JSM SVGFontElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFontElement
SVGFontElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFontElement where
  makeObject :: SVGFontElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFontElement -> JSVal) -> SVGFontElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontElement -> JSVal
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 :: SVGFontElement -> JSM GType
typeGType SVGFontElement
_ = JSM GType
gTypeSVGFontElement
  {-# INLINE typeGType #-}

noSVGFontElement :: Maybe SVGFontElement
noSVGFontElement :: Maybe SVGFontElement
noSVGFontElement = Maybe SVGFontElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFontElement #-}

gTypeSVGFontElement :: JSM GType
gTypeSVGFontElement :: JSM GType
gTypeSVGFontElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFontElement"

-- | Functions for this inteface are in "JSDOM.SVGFontFaceElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFontFaceElement Mozilla SVGFontFaceElement documentation>
newtype SVGFontFaceElement = SVGFontFaceElement { SVGFontFaceElement -> JSVal
unSVGFontFaceElement :: JSVal }

instance PToJSVal SVGFontFaceElement where
  pToJSVal :: SVGFontFaceElement -> JSVal
pToJSVal = SVGFontFaceElement -> JSVal
unSVGFontFaceElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFontFaceElement where
  pFromJSVal :: JSVal -> SVGFontFaceElement
pFromJSVal = JSVal -> SVGFontFaceElement
SVGFontFaceElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFontFaceElement where
  toJSVal :: SVGFontFaceElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFontFaceElement -> JSVal) -> SVGFontFaceElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontFaceElement -> JSVal
unSVGFontFaceElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFontFaceElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFontFaceElement)
fromJSVal JSVal
v = (JSVal -> SVGFontFaceElement)
-> Maybe JSVal -> Maybe SVGFontFaceElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFontFaceElement
SVGFontFaceElement (Maybe JSVal -> Maybe SVGFontFaceElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFontFaceElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFontFaceElement
fromJSValUnchecked = SVGFontFaceElement -> JSM SVGFontFaceElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFontFaceElement -> JSM SVGFontFaceElement)
-> (JSVal -> SVGFontFaceElement) -> JSVal -> JSM SVGFontFaceElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFontFaceElement
SVGFontFaceElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFontFaceElement where
  makeObject :: SVGFontFaceElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFontFaceElement -> JSVal)
-> SVGFontFaceElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontFaceElement -> JSVal
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 :: SVGFontFaceElement -> JSM GType
typeGType SVGFontFaceElement
_ = JSM GType
gTypeSVGFontFaceElement
  {-# INLINE typeGType #-}

noSVGFontFaceElement :: Maybe SVGFontFaceElement
noSVGFontFaceElement :: Maybe SVGFontFaceElement
noSVGFontFaceElement = Maybe SVGFontFaceElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFontFaceElement #-}

gTypeSVGFontFaceElement :: JSM GType
gTypeSVGFontFaceElement :: JSM GType
gTypeSVGFontFaceElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFontFaceElement"

-- | Functions for this inteface are in "JSDOM.SVGFontFaceFormatElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFontFaceFormatElement Mozilla SVGFontFaceFormatElement documentation>
newtype SVGFontFaceFormatElement = SVGFontFaceFormatElement { SVGFontFaceFormatElement -> JSVal
unSVGFontFaceFormatElement :: JSVal }

instance PToJSVal SVGFontFaceFormatElement where
  pToJSVal :: SVGFontFaceFormatElement -> JSVal
pToJSVal = SVGFontFaceFormatElement -> JSVal
unSVGFontFaceFormatElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFontFaceFormatElement where
  pFromJSVal :: JSVal -> SVGFontFaceFormatElement
pFromJSVal = JSVal -> SVGFontFaceFormatElement
SVGFontFaceFormatElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFontFaceFormatElement where
  toJSVal :: SVGFontFaceFormatElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFontFaceFormatElement -> JSVal)
-> SVGFontFaceFormatElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontFaceFormatElement -> JSVal
unSVGFontFaceFormatElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFontFaceFormatElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFontFaceFormatElement)
fromJSVal JSVal
v = (JSVal -> SVGFontFaceFormatElement)
-> Maybe JSVal -> Maybe SVGFontFaceFormatElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFontFaceFormatElement
SVGFontFaceFormatElement (Maybe JSVal -> Maybe SVGFontFaceFormatElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFontFaceFormatElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFontFaceFormatElement
fromJSValUnchecked = SVGFontFaceFormatElement -> JSM SVGFontFaceFormatElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFontFaceFormatElement -> JSM SVGFontFaceFormatElement)
-> (JSVal -> SVGFontFaceFormatElement)
-> JSVal
-> JSM SVGFontFaceFormatElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFontFaceFormatElement
SVGFontFaceFormatElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFontFaceFormatElement where
  makeObject :: SVGFontFaceFormatElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFontFaceFormatElement -> JSVal)
-> SVGFontFaceFormatElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontFaceFormatElement -> JSVal
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 :: SVGFontFaceFormatElement -> JSM GType
typeGType SVGFontFaceFormatElement
_ = JSM GType
gTypeSVGFontFaceFormatElement
  {-# INLINE typeGType #-}

noSVGFontFaceFormatElement :: Maybe SVGFontFaceFormatElement
noSVGFontFaceFormatElement :: Maybe SVGFontFaceFormatElement
noSVGFontFaceFormatElement = Maybe SVGFontFaceFormatElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFontFaceFormatElement #-}

gTypeSVGFontFaceFormatElement :: JSM GType
gTypeSVGFontFaceFormatElement :: JSM GType
gTypeSVGFontFaceFormatElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFontFaceFormatElement"

-- | Functions for this inteface are in "JSDOM.SVGFontFaceNameElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFontFaceNameElement Mozilla SVGFontFaceNameElement documentation>
newtype SVGFontFaceNameElement = SVGFontFaceNameElement { SVGFontFaceNameElement -> JSVal
unSVGFontFaceNameElement :: JSVal }

instance PToJSVal SVGFontFaceNameElement where
  pToJSVal :: SVGFontFaceNameElement -> JSVal
pToJSVal = SVGFontFaceNameElement -> JSVal
unSVGFontFaceNameElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFontFaceNameElement where
  pFromJSVal :: JSVal -> SVGFontFaceNameElement
pFromJSVal = JSVal -> SVGFontFaceNameElement
SVGFontFaceNameElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFontFaceNameElement where
  toJSVal :: SVGFontFaceNameElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFontFaceNameElement -> JSVal)
-> SVGFontFaceNameElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontFaceNameElement -> JSVal
unSVGFontFaceNameElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFontFaceNameElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFontFaceNameElement)
fromJSVal JSVal
v = (JSVal -> SVGFontFaceNameElement)
-> Maybe JSVal -> Maybe SVGFontFaceNameElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFontFaceNameElement
SVGFontFaceNameElement (Maybe JSVal -> Maybe SVGFontFaceNameElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFontFaceNameElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFontFaceNameElement
fromJSValUnchecked = SVGFontFaceNameElement -> JSM SVGFontFaceNameElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFontFaceNameElement -> JSM SVGFontFaceNameElement)
-> (JSVal -> SVGFontFaceNameElement)
-> JSVal
-> JSM SVGFontFaceNameElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFontFaceNameElement
SVGFontFaceNameElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFontFaceNameElement where
  makeObject :: SVGFontFaceNameElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFontFaceNameElement -> JSVal)
-> SVGFontFaceNameElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontFaceNameElement -> JSVal
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 :: SVGFontFaceNameElement -> JSM GType
typeGType SVGFontFaceNameElement
_ = JSM GType
gTypeSVGFontFaceNameElement
  {-# INLINE typeGType #-}

noSVGFontFaceNameElement :: Maybe SVGFontFaceNameElement
noSVGFontFaceNameElement :: Maybe SVGFontFaceNameElement
noSVGFontFaceNameElement = Maybe SVGFontFaceNameElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFontFaceNameElement #-}

gTypeSVGFontFaceNameElement :: JSM GType
gTypeSVGFontFaceNameElement :: JSM GType
gTypeSVGFontFaceNameElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFontFaceNameElement"

-- | Functions for this inteface are in "JSDOM.SVGFontFaceSrcElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFontFaceSrcElement Mozilla SVGFontFaceSrcElement documentation>
newtype SVGFontFaceSrcElement = SVGFontFaceSrcElement { SVGFontFaceSrcElement -> JSVal
unSVGFontFaceSrcElement :: JSVal }

instance PToJSVal SVGFontFaceSrcElement where
  pToJSVal :: SVGFontFaceSrcElement -> JSVal
pToJSVal = SVGFontFaceSrcElement -> JSVal
unSVGFontFaceSrcElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFontFaceSrcElement where
  pFromJSVal :: JSVal -> SVGFontFaceSrcElement
pFromJSVal = JSVal -> SVGFontFaceSrcElement
SVGFontFaceSrcElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFontFaceSrcElement where
  toJSVal :: SVGFontFaceSrcElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFontFaceSrcElement -> JSVal)
-> SVGFontFaceSrcElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontFaceSrcElement -> JSVal
unSVGFontFaceSrcElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFontFaceSrcElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFontFaceSrcElement)
fromJSVal JSVal
v = (JSVal -> SVGFontFaceSrcElement)
-> Maybe JSVal -> Maybe SVGFontFaceSrcElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFontFaceSrcElement
SVGFontFaceSrcElement (Maybe JSVal -> Maybe SVGFontFaceSrcElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFontFaceSrcElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFontFaceSrcElement
fromJSValUnchecked = SVGFontFaceSrcElement -> JSM SVGFontFaceSrcElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFontFaceSrcElement -> JSM SVGFontFaceSrcElement)
-> (JSVal -> SVGFontFaceSrcElement)
-> JSVal
-> JSM SVGFontFaceSrcElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFontFaceSrcElement
SVGFontFaceSrcElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFontFaceSrcElement where
  makeObject :: SVGFontFaceSrcElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFontFaceSrcElement -> JSVal)
-> SVGFontFaceSrcElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontFaceSrcElement -> JSVal
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 :: SVGFontFaceSrcElement -> JSM GType
typeGType SVGFontFaceSrcElement
_ = JSM GType
gTypeSVGFontFaceSrcElement
  {-# INLINE typeGType #-}

noSVGFontFaceSrcElement :: Maybe SVGFontFaceSrcElement
noSVGFontFaceSrcElement :: Maybe SVGFontFaceSrcElement
noSVGFontFaceSrcElement = Maybe SVGFontFaceSrcElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFontFaceSrcElement #-}

gTypeSVGFontFaceSrcElement :: JSM GType
gTypeSVGFontFaceSrcElement :: JSM GType
gTypeSVGFontFaceSrcElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFontFaceSrcElement"

-- | Functions for this inteface are in "JSDOM.SVGFontFaceUriElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGFontFaceUriElement Mozilla SVGFontFaceUriElement documentation>
newtype SVGFontFaceUriElement = SVGFontFaceUriElement { SVGFontFaceUriElement -> JSVal
unSVGFontFaceUriElement :: JSVal }

instance PToJSVal SVGFontFaceUriElement where
  pToJSVal :: SVGFontFaceUriElement -> JSVal
pToJSVal = SVGFontFaceUriElement -> JSVal
unSVGFontFaceUriElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGFontFaceUriElement where
  pFromJSVal :: JSVal -> SVGFontFaceUriElement
pFromJSVal = JSVal -> SVGFontFaceUriElement
SVGFontFaceUriElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGFontFaceUriElement where
  toJSVal :: SVGFontFaceUriElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGFontFaceUriElement -> JSVal)
-> SVGFontFaceUriElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontFaceUriElement -> JSVal
unSVGFontFaceUriElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGFontFaceUriElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGFontFaceUriElement)
fromJSVal JSVal
v = (JSVal -> SVGFontFaceUriElement)
-> Maybe JSVal -> Maybe SVGFontFaceUriElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGFontFaceUriElement
SVGFontFaceUriElement (Maybe JSVal -> Maybe SVGFontFaceUriElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGFontFaceUriElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGFontFaceUriElement
fromJSValUnchecked = SVGFontFaceUriElement -> JSM SVGFontFaceUriElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGFontFaceUriElement -> JSM SVGFontFaceUriElement)
-> (JSVal -> SVGFontFaceUriElement)
-> JSVal
-> JSM SVGFontFaceUriElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGFontFaceUriElement
SVGFontFaceUriElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGFontFaceUriElement where
  makeObject :: SVGFontFaceUriElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGFontFaceUriElement -> JSVal)
-> SVGFontFaceUriElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGFontFaceUriElement -> JSVal
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 :: SVGFontFaceUriElement -> JSM GType
typeGType SVGFontFaceUriElement
_ = JSM GType
gTypeSVGFontFaceUriElement
  {-# INLINE typeGType #-}

noSVGFontFaceUriElement :: Maybe SVGFontFaceUriElement
noSVGFontFaceUriElement :: Maybe SVGFontFaceUriElement
noSVGFontFaceUriElement = Maybe SVGFontFaceUriElement
forall a. Maybe a
Nothing
{-# INLINE noSVGFontFaceUriElement #-}

gTypeSVGFontFaceUriElement :: JSM GType
gTypeSVGFontFaceUriElement :: JSM GType
gTypeSVGFontFaceUriElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGFontFaceUriElement"

-- | Functions for this inteface are in "JSDOM.SVGForeignObjectElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGForeignObjectElement Mozilla SVGForeignObjectElement documentation>
newtype SVGForeignObjectElement = SVGForeignObjectElement { SVGForeignObjectElement -> JSVal
unSVGForeignObjectElement :: JSVal }

instance PToJSVal SVGForeignObjectElement where
  pToJSVal :: SVGForeignObjectElement -> JSVal
pToJSVal = SVGForeignObjectElement -> JSVal
unSVGForeignObjectElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGForeignObjectElement where
  pFromJSVal :: JSVal -> SVGForeignObjectElement
pFromJSVal = JSVal -> SVGForeignObjectElement
SVGForeignObjectElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGForeignObjectElement where
  toJSVal :: SVGForeignObjectElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGForeignObjectElement -> JSVal)
-> SVGForeignObjectElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGForeignObjectElement -> JSVal
unSVGForeignObjectElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGForeignObjectElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGForeignObjectElement)
fromJSVal JSVal
v = (JSVal -> SVGForeignObjectElement)
-> Maybe JSVal -> Maybe SVGForeignObjectElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGForeignObjectElement
SVGForeignObjectElement (Maybe JSVal -> Maybe SVGForeignObjectElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGForeignObjectElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGForeignObjectElement
fromJSValUnchecked = SVGForeignObjectElement -> JSM SVGForeignObjectElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGForeignObjectElement -> JSM SVGForeignObjectElement)
-> (JSVal -> SVGForeignObjectElement)
-> JSVal
-> JSM SVGForeignObjectElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGForeignObjectElement
SVGForeignObjectElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGForeignObjectElement where
  makeObject :: SVGForeignObjectElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGForeignObjectElement -> JSVal)
-> SVGForeignObjectElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGForeignObjectElement -> JSVal
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 :: SVGForeignObjectElement -> JSM GType
typeGType SVGForeignObjectElement
_ = JSM GType
gTypeSVGForeignObjectElement
  {-# INLINE typeGType #-}

noSVGForeignObjectElement :: Maybe SVGForeignObjectElement
noSVGForeignObjectElement :: Maybe SVGForeignObjectElement
noSVGForeignObjectElement = Maybe SVGForeignObjectElement
forall a. Maybe a
Nothing
{-# INLINE noSVGForeignObjectElement #-}

gTypeSVGForeignObjectElement :: JSM GType
gTypeSVGForeignObjectElement :: JSM GType
gTypeSVGForeignObjectElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGForeignObjectElement"

-- | Functions for this inteface are in "JSDOM.SVGGElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGGElement Mozilla SVGGElement documentation>
newtype SVGGElement = SVGGElement { SVGGElement -> JSVal
unSVGGElement :: JSVal }

instance PToJSVal SVGGElement where
  pToJSVal :: SVGGElement -> JSVal
pToJSVal = SVGGElement -> JSVal
unSVGGElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGGElement where
  pFromJSVal :: JSVal -> SVGGElement
pFromJSVal = JSVal -> SVGGElement
SVGGElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGGElement where
  toJSVal :: SVGGElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGGElement -> JSVal) -> SVGGElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGGElement -> JSVal
unSVGGElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGGElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGGElement)
fromJSVal JSVal
v = (JSVal -> SVGGElement) -> Maybe JSVal -> Maybe SVGGElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGGElement
SVGGElement (Maybe JSVal -> Maybe SVGGElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGGElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGGElement
fromJSValUnchecked = SVGGElement -> JSM SVGGElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGGElement -> JSM SVGGElement)
-> (JSVal -> SVGGElement) -> JSVal -> JSM SVGGElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGGElement
SVGGElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGGElement where
  makeObject :: SVGGElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGGElement -> JSVal) -> SVGGElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGGElement -> JSVal
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 :: SVGGElement -> JSM GType
typeGType SVGGElement
_ = JSM GType
gTypeSVGGElement
  {-# INLINE typeGType #-}

noSVGGElement :: Maybe SVGGElement
noSVGGElement :: Maybe SVGGElement
noSVGGElement = Maybe SVGGElement
forall a. Maybe a
Nothing
{-# INLINE noSVGGElement #-}

gTypeSVGGElement :: JSM GType
gTypeSVGGElement :: JSM GType
gTypeSVGGElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGGElement"

-- | Functions for this inteface are in "JSDOM.SVGGlyphElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGGlyphElement Mozilla SVGGlyphElement documentation>
newtype SVGGlyphElement = SVGGlyphElement { SVGGlyphElement -> JSVal
unSVGGlyphElement :: JSVal }

instance PToJSVal SVGGlyphElement where
  pToJSVal :: SVGGlyphElement -> JSVal
pToJSVal = SVGGlyphElement -> JSVal
unSVGGlyphElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGGlyphElement where
  pFromJSVal :: JSVal -> SVGGlyphElement
pFromJSVal = JSVal -> SVGGlyphElement
SVGGlyphElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGGlyphElement where
  toJSVal :: SVGGlyphElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGGlyphElement -> JSVal) -> SVGGlyphElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGGlyphElement -> JSVal
unSVGGlyphElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGGlyphElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGGlyphElement)
fromJSVal JSVal
v = (JSVal -> SVGGlyphElement) -> Maybe JSVal -> Maybe SVGGlyphElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGGlyphElement
SVGGlyphElement (Maybe JSVal -> Maybe SVGGlyphElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGGlyphElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGGlyphElement
fromJSValUnchecked = SVGGlyphElement -> JSM SVGGlyphElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGGlyphElement -> JSM SVGGlyphElement)
-> (JSVal -> SVGGlyphElement) -> JSVal -> JSM SVGGlyphElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGGlyphElement
SVGGlyphElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGGlyphElement where
  makeObject :: SVGGlyphElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGGlyphElement -> JSVal) -> SVGGlyphElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGGlyphElement -> JSVal
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 :: SVGGlyphElement -> JSM GType
typeGType SVGGlyphElement
_ = JSM GType
gTypeSVGGlyphElement
  {-# INLINE typeGType #-}

noSVGGlyphElement :: Maybe SVGGlyphElement
noSVGGlyphElement :: Maybe SVGGlyphElement
noSVGGlyphElement = Maybe SVGGlyphElement
forall a. Maybe a
Nothing
{-# INLINE noSVGGlyphElement #-}

gTypeSVGGlyphElement :: JSM GType
gTypeSVGGlyphElement :: JSM GType
gTypeSVGGlyphElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGGlyphElement"

-- | Functions for this inteface are in "JSDOM.SVGGlyphRefElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGURIReference"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGGlyphRefElement Mozilla SVGGlyphRefElement documentation>
newtype SVGGlyphRefElement = SVGGlyphRefElement { SVGGlyphRefElement -> JSVal
unSVGGlyphRefElement :: JSVal }

instance PToJSVal SVGGlyphRefElement where
  pToJSVal :: SVGGlyphRefElement -> JSVal
pToJSVal = SVGGlyphRefElement -> JSVal
unSVGGlyphRefElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGGlyphRefElement where
  pFromJSVal :: JSVal -> SVGGlyphRefElement
pFromJSVal = JSVal -> SVGGlyphRefElement
SVGGlyphRefElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGGlyphRefElement where
  toJSVal :: SVGGlyphRefElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGGlyphRefElement -> JSVal) -> SVGGlyphRefElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGGlyphRefElement -> JSVal
unSVGGlyphRefElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGGlyphRefElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGGlyphRefElement)
fromJSVal JSVal
v = (JSVal -> SVGGlyphRefElement)
-> Maybe JSVal -> Maybe SVGGlyphRefElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGGlyphRefElement
SVGGlyphRefElement (Maybe JSVal -> Maybe SVGGlyphRefElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGGlyphRefElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGGlyphRefElement
fromJSValUnchecked = SVGGlyphRefElement -> JSM SVGGlyphRefElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGGlyphRefElement -> JSM SVGGlyphRefElement)
-> (JSVal -> SVGGlyphRefElement) -> JSVal -> JSM SVGGlyphRefElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGGlyphRefElement
SVGGlyphRefElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGGlyphRefElement where
  makeObject :: SVGGlyphRefElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGGlyphRefElement -> JSVal)
-> SVGGlyphRefElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGGlyphRefElement -> JSVal
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 :: SVGGlyphRefElement -> JSM GType
typeGType SVGGlyphRefElement
_ = JSM GType
gTypeSVGGlyphRefElement
  {-# INLINE typeGType #-}

noSVGGlyphRefElement :: Maybe SVGGlyphRefElement
noSVGGlyphRefElement :: Maybe SVGGlyphRefElement
noSVGGlyphRefElement = Maybe SVGGlyphRefElement
forall a. Maybe a
Nothing
{-# INLINE noSVGGlyphRefElement #-}

gTypeSVGGlyphRefElement :: JSM GType
gTypeSVGGlyphRefElement :: JSM GType
gTypeSVGGlyphRefElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGGlyphRefElement"

-- | Functions for this inteface are in "JSDOM.SVGGradientElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGGradientElement Mozilla SVGGradientElement documentation>
newtype SVGGradientElement = SVGGradientElement { SVGGradientElement -> JSVal
unSVGGradientElement :: JSVal }

instance PToJSVal SVGGradientElement where
  pToJSVal :: SVGGradientElement -> JSVal
pToJSVal = SVGGradientElement -> JSVal
unSVGGradientElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGGradientElement where
  pFromJSVal :: JSVal -> SVGGradientElement
pFromJSVal = JSVal -> SVGGradientElement
SVGGradientElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGGradientElement where
  toJSVal :: SVGGradientElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGGradientElement -> JSVal) -> SVGGradientElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGGradientElement -> JSVal
unSVGGradientElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGGradientElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGGradientElement)
fromJSVal JSVal
v = (JSVal -> SVGGradientElement)
-> Maybe JSVal -> Maybe SVGGradientElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGGradientElement
SVGGradientElement (Maybe JSVal -> Maybe SVGGradientElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGGradientElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGGradientElement
fromJSValUnchecked = SVGGradientElement -> JSM SVGGradientElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGGradientElement -> JSM SVGGradientElement)
-> (JSVal -> SVGGradientElement) -> JSVal -> JSM SVGGradientElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGGradientElement
SVGGradientElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGGradientElement where
  makeObject :: SVGGradientElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGGradientElement -> JSVal)
-> SVGGradientElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGGradientElement -> JSVal
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 :: forall o. IsSVGGradientElement o => o -> SVGGradientElement
toSVGGradientElement = JSVal -> SVGGradientElement
SVGGradientElement (JSVal -> SVGGradientElement)
-> (o -> JSVal) -> o -> SVGGradientElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: SVGGradientElement -> JSM GType
typeGType SVGGradientElement
_ = JSM GType
gTypeSVGGradientElement
  {-# INLINE typeGType #-}

noSVGGradientElement :: Maybe SVGGradientElement
noSVGGradientElement :: Maybe SVGGradientElement
noSVGGradientElement = Maybe SVGGradientElement
forall a. Maybe a
Nothing
{-# INLINE noSVGGradientElement #-}

gTypeSVGGradientElement :: JSM GType
gTypeSVGGradientElement :: JSM GType
gTypeSVGGradientElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGGradientElement"

-- | Functions for this inteface are in "JSDOM.SVGGraphicsElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGGraphicsElement Mozilla SVGGraphicsElement documentation>
newtype SVGGraphicsElement = SVGGraphicsElement { SVGGraphicsElement -> JSVal
unSVGGraphicsElement :: JSVal }

instance PToJSVal SVGGraphicsElement where
  pToJSVal :: SVGGraphicsElement -> JSVal
pToJSVal = SVGGraphicsElement -> JSVal
unSVGGraphicsElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGGraphicsElement where
  pFromJSVal :: JSVal -> SVGGraphicsElement
pFromJSVal = JSVal -> SVGGraphicsElement
SVGGraphicsElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGGraphicsElement where
  toJSVal :: SVGGraphicsElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGGraphicsElement -> JSVal) -> SVGGraphicsElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGGraphicsElement -> JSVal
unSVGGraphicsElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGGraphicsElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGGraphicsElement)
fromJSVal JSVal
v = (JSVal -> SVGGraphicsElement)
-> Maybe JSVal -> Maybe SVGGraphicsElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGGraphicsElement
SVGGraphicsElement (Maybe JSVal -> Maybe SVGGraphicsElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGGraphicsElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGGraphicsElement
fromJSValUnchecked = SVGGraphicsElement -> JSM SVGGraphicsElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGGraphicsElement -> JSM SVGGraphicsElement)
-> (JSVal -> SVGGraphicsElement) -> JSVal -> JSM SVGGraphicsElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGGraphicsElement
SVGGraphicsElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGGraphicsElement where
  makeObject :: SVGGraphicsElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGGraphicsElement -> JSVal)
-> SVGGraphicsElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGGraphicsElement -> JSVal
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 :: forall o. IsSVGGraphicsElement o => o -> SVGGraphicsElement
toSVGGraphicsElement = JSVal -> SVGGraphicsElement
SVGGraphicsElement (JSVal -> SVGGraphicsElement)
-> (o -> JSVal) -> o -> SVGGraphicsElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: SVGGraphicsElement -> JSM GType
typeGType SVGGraphicsElement
_ = JSM GType
gTypeSVGGraphicsElement
  {-# INLINE typeGType #-}

noSVGGraphicsElement :: Maybe SVGGraphicsElement
noSVGGraphicsElement :: Maybe SVGGraphicsElement
noSVGGraphicsElement = Maybe SVGGraphicsElement
forall a. Maybe a
Nothing
{-# INLINE noSVGGraphicsElement #-}

gTypeSVGGraphicsElement :: JSM GType
gTypeSVGGraphicsElement :: JSM GType
gTypeSVGGraphicsElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGGraphicsElement"

-- | Functions for this inteface are in "JSDOM.SVGHKernElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGHKernElement Mozilla SVGHKernElement documentation>
newtype SVGHKernElement = SVGHKernElement { SVGHKernElement -> JSVal
unSVGHKernElement :: JSVal }

instance PToJSVal SVGHKernElement where
  pToJSVal :: SVGHKernElement -> JSVal
pToJSVal = SVGHKernElement -> JSVal
unSVGHKernElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGHKernElement where
  pFromJSVal :: JSVal -> SVGHKernElement
pFromJSVal = JSVal -> SVGHKernElement
SVGHKernElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGHKernElement where
  toJSVal :: SVGHKernElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGHKernElement -> JSVal) -> SVGHKernElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGHKernElement -> JSVal
unSVGHKernElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGHKernElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGHKernElement)
fromJSVal JSVal
v = (JSVal -> SVGHKernElement) -> Maybe JSVal -> Maybe SVGHKernElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGHKernElement
SVGHKernElement (Maybe JSVal -> Maybe SVGHKernElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGHKernElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGHKernElement
fromJSValUnchecked = SVGHKernElement -> JSM SVGHKernElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGHKernElement -> JSM SVGHKernElement)
-> (JSVal -> SVGHKernElement) -> JSVal -> JSM SVGHKernElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGHKernElement
SVGHKernElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGHKernElement where
  makeObject :: SVGHKernElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGHKernElement -> JSVal) -> SVGHKernElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGHKernElement -> JSVal
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 :: SVGHKernElement -> JSM GType
typeGType SVGHKernElement
_ = JSM GType
gTypeSVGHKernElement
  {-# INLINE typeGType #-}

noSVGHKernElement :: Maybe SVGHKernElement
noSVGHKernElement :: Maybe SVGHKernElement
noSVGHKernElement = Maybe SVGHKernElement
forall a. Maybe a
Nothing
{-# INLINE noSVGHKernElement #-}

gTypeSVGHKernElement :: JSM GType
gTypeSVGHKernElement :: JSM GType
gTypeSVGHKernElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGHKernElement"

-- | Functions for this inteface are in "JSDOM.SVGImageElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGImageElement Mozilla SVGImageElement documentation>
newtype SVGImageElement = SVGImageElement { SVGImageElement -> JSVal
unSVGImageElement :: JSVal }

instance PToJSVal SVGImageElement where
  pToJSVal :: SVGImageElement -> JSVal
pToJSVal = SVGImageElement -> JSVal
unSVGImageElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGImageElement where
  pFromJSVal :: JSVal -> SVGImageElement
pFromJSVal = JSVal -> SVGImageElement
SVGImageElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGImageElement where
  toJSVal :: SVGImageElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGImageElement -> JSVal) -> SVGImageElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGImageElement -> JSVal
unSVGImageElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGImageElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGImageElement)
fromJSVal JSVal
v = (JSVal -> SVGImageElement) -> Maybe JSVal -> Maybe SVGImageElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGImageElement
SVGImageElement (Maybe JSVal -> Maybe SVGImageElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGImageElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGImageElement
fromJSValUnchecked = SVGImageElement -> JSM SVGImageElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGImageElement -> JSM SVGImageElement)
-> (JSVal -> SVGImageElement) -> JSVal -> JSM SVGImageElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGImageElement
SVGImageElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGImageElement where
  makeObject :: SVGImageElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGImageElement -> JSVal) -> SVGImageElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGImageElement -> JSVal
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 :: SVGImageElement -> JSM GType
typeGType SVGImageElement
_ = JSM GType
gTypeSVGImageElement
  {-# INLINE typeGType #-}

noSVGImageElement :: Maybe SVGImageElement
noSVGImageElement :: Maybe SVGImageElement
noSVGImageElement = Maybe SVGImageElement
forall a. Maybe a
Nothing
{-# INLINE noSVGImageElement #-}

gTypeSVGImageElement :: JSM GType
gTypeSVGImageElement :: JSM GType
gTypeSVGImageElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGImageElement"

-- | Functions for this inteface are in "JSDOM.SVGLength".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGLength Mozilla SVGLength documentation>
newtype SVGLength = SVGLength { SVGLength -> JSVal
unSVGLength :: JSVal }

instance PToJSVal SVGLength where
  pToJSVal :: SVGLength -> JSVal
pToJSVal = SVGLength -> JSVal
unSVGLength
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGLength where
  pFromJSVal :: JSVal -> SVGLength
pFromJSVal = JSVal -> SVGLength
SVGLength
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGLength where
  toJSVal :: SVGLength -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGLength -> JSVal) -> SVGLength -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGLength -> JSVal
unSVGLength
  {-# INLINE toJSVal #-}

instance FromJSVal SVGLength where
  fromJSVal :: JSVal -> JSM (Maybe SVGLength)
fromJSVal JSVal
v = (JSVal -> SVGLength) -> Maybe JSVal -> Maybe SVGLength
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGLength
SVGLength (Maybe JSVal -> Maybe SVGLength)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGLength)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGLength
fromJSValUnchecked = SVGLength -> JSM SVGLength
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGLength -> JSM SVGLength)
-> (JSVal -> SVGLength) -> JSVal -> JSM SVGLength
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGLength
SVGLength
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGLength where
  makeObject :: SVGLength -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGLength -> JSVal) -> SVGLength -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGLength -> JSVal
unSVGLength

instance IsGObject SVGLength where
  typeGType :: SVGLength -> JSM GType
typeGType SVGLength
_ = JSM GType
gTypeSVGLength
  {-# INLINE typeGType #-}

noSVGLength :: Maybe SVGLength
noSVGLength :: Maybe SVGLength
noSVGLength = Maybe SVGLength
forall a. Maybe a
Nothing
{-# INLINE noSVGLength #-}

gTypeSVGLength :: JSM GType
gTypeSVGLength :: JSM GType
gTypeSVGLength = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGLength"

-- | Functions for this inteface are in "JSDOM.SVGLengthList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGLengthList Mozilla SVGLengthList documentation>
newtype SVGLengthList = SVGLengthList { SVGLengthList -> JSVal
unSVGLengthList :: JSVal }

instance PToJSVal SVGLengthList where
  pToJSVal :: SVGLengthList -> JSVal
pToJSVal = SVGLengthList -> JSVal
unSVGLengthList
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGLengthList where
  pFromJSVal :: JSVal -> SVGLengthList
pFromJSVal = JSVal -> SVGLengthList
SVGLengthList
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGLengthList where
  toJSVal :: SVGLengthList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGLengthList -> JSVal) -> SVGLengthList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGLengthList -> JSVal
unSVGLengthList
  {-# INLINE toJSVal #-}

instance FromJSVal SVGLengthList where
  fromJSVal :: JSVal -> JSM (Maybe SVGLengthList)
fromJSVal JSVal
v = (JSVal -> SVGLengthList) -> Maybe JSVal -> Maybe SVGLengthList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGLengthList
SVGLengthList (Maybe JSVal -> Maybe SVGLengthList)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGLengthList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGLengthList
fromJSValUnchecked = SVGLengthList -> JSM SVGLengthList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGLengthList -> JSM SVGLengthList)
-> (JSVal -> SVGLengthList) -> JSVal -> JSM SVGLengthList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGLengthList
SVGLengthList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGLengthList where
  makeObject :: SVGLengthList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGLengthList -> JSVal) -> SVGLengthList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGLengthList -> JSVal
unSVGLengthList

instance IsGObject SVGLengthList where
  typeGType :: SVGLengthList -> JSM GType
typeGType SVGLengthList
_ = JSM GType
gTypeSVGLengthList
  {-# INLINE typeGType #-}

noSVGLengthList :: Maybe SVGLengthList
noSVGLengthList :: Maybe SVGLengthList
noSVGLengthList = Maybe SVGLengthList
forall a. Maybe a
Nothing
{-# INLINE noSVGLengthList #-}

gTypeSVGLengthList :: JSM GType
gTypeSVGLengthList :: JSM GType
gTypeSVGLengthList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGLengthList"

-- | Functions for this inteface are in "JSDOM.SVGLineElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGLineElement Mozilla SVGLineElement documentation>
newtype SVGLineElement = SVGLineElement { SVGLineElement -> JSVal
unSVGLineElement :: JSVal }

instance PToJSVal SVGLineElement where
  pToJSVal :: SVGLineElement -> JSVal
pToJSVal = SVGLineElement -> JSVal
unSVGLineElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGLineElement where
  pFromJSVal :: JSVal -> SVGLineElement
pFromJSVal = JSVal -> SVGLineElement
SVGLineElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGLineElement where
  toJSVal :: SVGLineElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGLineElement -> JSVal) -> SVGLineElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGLineElement -> JSVal
unSVGLineElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGLineElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGLineElement)
fromJSVal JSVal
v = (JSVal -> SVGLineElement) -> Maybe JSVal -> Maybe SVGLineElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGLineElement
SVGLineElement (Maybe JSVal -> Maybe SVGLineElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGLineElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGLineElement
fromJSValUnchecked = SVGLineElement -> JSM SVGLineElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGLineElement -> JSM SVGLineElement)
-> (JSVal -> SVGLineElement) -> JSVal -> JSM SVGLineElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGLineElement
SVGLineElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGLineElement where
  makeObject :: SVGLineElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGLineElement -> JSVal) -> SVGLineElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGLineElement -> JSVal
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 :: SVGLineElement -> JSM GType
typeGType SVGLineElement
_ = JSM GType
gTypeSVGLineElement
  {-# INLINE typeGType #-}

noSVGLineElement :: Maybe SVGLineElement
noSVGLineElement :: Maybe SVGLineElement
noSVGLineElement = Maybe SVGLineElement
forall a. Maybe a
Nothing
{-# INLINE noSVGLineElement #-}

gTypeSVGLineElement :: JSM GType
gTypeSVGLineElement :: JSM GType
gTypeSVGLineElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGLineElement"

-- | Functions for this inteface are in "JSDOM.SVGLinearGradientElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGradientElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGLinearGradientElement Mozilla SVGLinearGradientElement documentation>
newtype SVGLinearGradientElement = SVGLinearGradientElement { SVGLinearGradientElement -> JSVal
unSVGLinearGradientElement :: JSVal }

instance PToJSVal SVGLinearGradientElement where
  pToJSVal :: SVGLinearGradientElement -> JSVal
pToJSVal = SVGLinearGradientElement -> JSVal
unSVGLinearGradientElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGLinearGradientElement where
  pFromJSVal :: JSVal -> SVGLinearGradientElement
pFromJSVal = JSVal -> SVGLinearGradientElement
SVGLinearGradientElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGLinearGradientElement where
  toJSVal :: SVGLinearGradientElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGLinearGradientElement -> JSVal)
-> SVGLinearGradientElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGLinearGradientElement -> JSVal
unSVGLinearGradientElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGLinearGradientElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGLinearGradientElement)
fromJSVal JSVal
v = (JSVal -> SVGLinearGradientElement)
-> Maybe JSVal -> Maybe SVGLinearGradientElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGLinearGradientElement
SVGLinearGradientElement (Maybe JSVal -> Maybe SVGLinearGradientElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGLinearGradientElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGLinearGradientElement
fromJSValUnchecked = SVGLinearGradientElement -> JSM SVGLinearGradientElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGLinearGradientElement -> JSM SVGLinearGradientElement)
-> (JSVal -> SVGLinearGradientElement)
-> JSVal
-> JSM SVGLinearGradientElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGLinearGradientElement
SVGLinearGradientElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGLinearGradientElement where
  makeObject :: SVGLinearGradientElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGLinearGradientElement -> JSVal)
-> SVGLinearGradientElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGLinearGradientElement -> JSVal
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 :: SVGLinearGradientElement -> JSM GType
typeGType SVGLinearGradientElement
_ = JSM GType
gTypeSVGLinearGradientElement
  {-# INLINE typeGType #-}

noSVGLinearGradientElement :: Maybe SVGLinearGradientElement
noSVGLinearGradientElement :: Maybe SVGLinearGradientElement
noSVGLinearGradientElement = Maybe SVGLinearGradientElement
forall a. Maybe a
Nothing
{-# INLINE noSVGLinearGradientElement #-}

gTypeSVGLinearGradientElement :: JSM GType
gTypeSVGLinearGradientElement :: JSM GType
gTypeSVGLinearGradientElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGLinearGradientElement"

-- | Functions for this inteface are in "JSDOM.SVGMPathElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGMPathElement Mozilla SVGMPathElement documentation>
newtype SVGMPathElement = SVGMPathElement { SVGMPathElement -> JSVal
unSVGMPathElement :: JSVal }

instance PToJSVal SVGMPathElement where
  pToJSVal :: SVGMPathElement -> JSVal
pToJSVal = SVGMPathElement -> JSVal
unSVGMPathElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGMPathElement where
  pFromJSVal :: JSVal -> SVGMPathElement
pFromJSVal = JSVal -> SVGMPathElement
SVGMPathElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGMPathElement where
  toJSVal :: SVGMPathElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGMPathElement -> JSVal) -> SVGMPathElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMPathElement -> JSVal
unSVGMPathElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGMPathElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGMPathElement)
fromJSVal JSVal
v = (JSVal -> SVGMPathElement) -> Maybe JSVal -> Maybe SVGMPathElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGMPathElement
SVGMPathElement (Maybe JSVal -> Maybe SVGMPathElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGMPathElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGMPathElement
fromJSValUnchecked = SVGMPathElement -> JSM SVGMPathElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGMPathElement -> JSM SVGMPathElement)
-> (JSVal -> SVGMPathElement) -> JSVal -> JSM SVGMPathElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGMPathElement
SVGMPathElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGMPathElement where
  makeObject :: SVGMPathElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGMPathElement -> JSVal) -> SVGMPathElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMPathElement -> JSVal
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 :: SVGMPathElement -> JSM GType
typeGType SVGMPathElement
_ = JSM GType
gTypeSVGMPathElement
  {-# INLINE typeGType #-}

noSVGMPathElement :: Maybe SVGMPathElement
noSVGMPathElement :: Maybe SVGMPathElement
noSVGMPathElement = Maybe SVGMPathElement
forall a. Maybe a
Nothing
{-# INLINE noSVGMPathElement #-}

gTypeSVGMPathElement :: JSM GType
gTypeSVGMPathElement :: JSM GType
gTypeSVGMPathElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGMPathElement"

-- | Functions for this inteface are in "JSDOM.SVGMarkerElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFitToViewBox"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGMarkerElement Mozilla SVGMarkerElement documentation>
newtype SVGMarkerElement = SVGMarkerElement { SVGMarkerElement -> JSVal
unSVGMarkerElement :: JSVal }

instance PToJSVal SVGMarkerElement where
  pToJSVal :: SVGMarkerElement -> JSVal
pToJSVal = SVGMarkerElement -> JSVal
unSVGMarkerElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGMarkerElement where
  pFromJSVal :: JSVal -> SVGMarkerElement
pFromJSVal = JSVal -> SVGMarkerElement
SVGMarkerElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGMarkerElement where
  toJSVal :: SVGMarkerElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGMarkerElement -> JSVal) -> SVGMarkerElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMarkerElement -> JSVal
unSVGMarkerElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGMarkerElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGMarkerElement)
fromJSVal JSVal
v = (JSVal -> SVGMarkerElement)
-> Maybe JSVal -> Maybe SVGMarkerElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGMarkerElement
SVGMarkerElement (Maybe JSVal -> Maybe SVGMarkerElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGMarkerElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGMarkerElement
fromJSValUnchecked = SVGMarkerElement -> JSM SVGMarkerElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGMarkerElement -> JSM SVGMarkerElement)
-> (JSVal -> SVGMarkerElement) -> JSVal -> JSM SVGMarkerElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGMarkerElement
SVGMarkerElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGMarkerElement where
  makeObject :: SVGMarkerElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGMarkerElement -> JSVal) -> SVGMarkerElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMarkerElement -> JSVal
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 :: SVGMarkerElement -> JSM GType
typeGType SVGMarkerElement
_ = JSM GType
gTypeSVGMarkerElement
  {-# INLINE typeGType #-}

noSVGMarkerElement :: Maybe SVGMarkerElement
noSVGMarkerElement :: Maybe SVGMarkerElement
noSVGMarkerElement = Maybe SVGMarkerElement
forall a. Maybe a
Nothing
{-# INLINE noSVGMarkerElement #-}

gTypeSVGMarkerElement :: JSM GType
gTypeSVGMarkerElement :: JSM GType
gTypeSVGMarkerElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGMarkerElement"

-- | Functions for this inteface are in "JSDOM.SVGMaskElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGMaskElement Mozilla SVGMaskElement documentation>
newtype SVGMaskElement = SVGMaskElement { SVGMaskElement -> JSVal
unSVGMaskElement :: JSVal }

instance PToJSVal SVGMaskElement where
  pToJSVal :: SVGMaskElement -> JSVal
pToJSVal = SVGMaskElement -> JSVal
unSVGMaskElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGMaskElement where
  pFromJSVal :: JSVal -> SVGMaskElement
pFromJSVal = JSVal -> SVGMaskElement
SVGMaskElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGMaskElement where
  toJSVal :: SVGMaskElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGMaskElement -> JSVal) -> SVGMaskElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMaskElement -> JSVal
unSVGMaskElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGMaskElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGMaskElement)
fromJSVal JSVal
v = (JSVal -> SVGMaskElement) -> Maybe JSVal -> Maybe SVGMaskElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGMaskElement
SVGMaskElement (Maybe JSVal -> Maybe SVGMaskElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGMaskElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGMaskElement
fromJSValUnchecked = SVGMaskElement -> JSM SVGMaskElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGMaskElement -> JSM SVGMaskElement)
-> (JSVal -> SVGMaskElement) -> JSVal -> JSM SVGMaskElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGMaskElement
SVGMaskElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGMaskElement where
  makeObject :: SVGMaskElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGMaskElement -> JSVal) -> SVGMaskElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMaskElement -> JSVal
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 :: SVGMaskElement -> JSM GType
typeGType SVGMaskElement
_ = JSM GType
gTypeSVGMaskElement
  {-# INLINE typeGType #-}

noSVGMaskElement :: Maybe SVGMaskElement
noSVGMaskElement :: Maybe SVGMaskElement
noSVGMaskElement = Maybe SVGMaskElement
forall a. Maybe a
Nothing
{-# INLINE noSVGMaskElement #-}

gTypeSVGMaskElement :: JSM GType
gTypeSVGMaskElement :: JSM GType
gTypeSVGMaskElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGMaskElement"

-- | Functions for this inteface are in "JSDOM.SVGMatrix".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGMatrix Mozilla SVGMatrix documentation>
newtype SVGMatrix = SVGMatrix { SVGMatrix -> JSVal
unSVGMatrix :: JSVal }

instance PToJSVal SVGMatrix where
  pToJSVal :: SVGMatrix -> JSVal
pToJSVal = SVGMatrix -> JSVal
unSVGMatrix
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGMatrix where
  pFromJSVal :: JSVal -> SVGMatrix
pFromJSVal = JSVal -> SVGMatrix
SVGMatrix
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGMatrix where
  toJSVal :: SVGMatrix -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGMatrix -> JSVal) -> SVGMatrix -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMatrix -> JSVal
unSVGMatrix
  {-# INLINE toJSVal #-}

instance FromJSVal SVGMatrix where
  fromJSVal :: JSVal -> JSM (Maybe SVGMatrix)
fromJSVal JSVal
v = (JSVal -> SVGMatrix) -> Maybe JSVal -> Maybe SVGMatrix
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGMatrix
SVGMatrix (Maybe JSVal -> Maybe SVGMatrix)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGMatrix)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGMatrix
fromJSValUnchecked = SVGMatrix -> JSM SVGMatrix
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGMatrix -> JSM SVGMatrix)
-> (JSVal -> SVGMatrix) -> JSVal -> JSM SVGMatrix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGMatrix
SVGMatrix
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGMatrix where
  makeObject :: SVGMatrix -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGMatrix -> JSVal) -> SVGMatrix -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMatrix -> JSVal
unSVGMatrix

instance IsGObject SVGMatrix where
  typeGType :: SVGMatrix -> JSM GType
typeGType SVGMatrix
_ = JSM GType
gTypeSVGMatrix
  {-# INLINE typeGType #-}

noSVGMatrix :: Maybe SVGMatrix
noSVGMatrix :: Maybe SVGMatrix
noSVGMatrix = Maybe SVGMatrix
forall a. Maybe a
Nothing
{-# INLINE noSVGMatrix #-}

gTypeSVGMatrix :: JSM GType
gTypeSVGMatrix :: JSM GType
gTypeSVGMatrix = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGMatrix"

-- | Functions for this inteface are in "JSDOM.SVGMetadataElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGMetadataElement Mozilla SVGMetadataElement documentation>
newtype SVGMetadataElement = SVGMetadataElement { SVGMetadataElement -> JSVal
unSVGMetadataElement :: JSVal }

instance PToJSVal SVGMetadataElement where
  pToJSVal :: SVGMetadataElement -> JSVal
pToJSVal = SVGMetadataElement -> JSVal
unSVGMetadataElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGMetadataElement where
  pFromJSVal :: JSVal -> SVGMetadataElement
pFromJSVal = JSVal -> SVGMetadataElement
SVGMetadataElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGMetadataElement where
  toJSVal :: SVGMetadataElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGMetadataElement -> JSVal) -> SVGMetadataElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMetadataElement -> JSVal
unSVGMetadataElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGMetadataElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGMetadataElement)
fromJSVal JSVal
v = (JSVal -> SVGMetadataElement)
-> Maybe JSVal -> Maybe SVGMetadataElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGMetadataElement
SVGMetadataElement (Maybe JSVal -> Maybe SVGMetadataElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGMetadataElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGMetadataElement
fromJSValUnchecked = SVGMetadataElement -> JSM SVGMetadataElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGMetadataElement -> JSM SVGMetadataElement)
-> (JSVal -> SVGMetadataElement) -> JSVal -> JSM SVGMetadataElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGMetadataElement
SVGMetadataElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGMetadataElement where
  makeObject :: SVGMetadataElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGMetadataElement -> JSVal)
-> SVGMetadataElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMetadataElement -> JSVal
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 :: SVGMetadataElement -> JSM GType
typeGType SVGMetadataElement
_ = JSM GType
gTypeSVGMetadataElement
  {-# INLINE typeGType #-}

noSVGMetadataElement :: Maybe SVGMetadataElement
noSVGMetadataElement :: Maybe SVGMetadataElement
noSVGMetadataElement = Maybe SVGMetadataElement
forall a. Maybe a
Nothing
{-# INLINE noSVGMetadataElement #-}

gTypeSVGMetadataElement :: JSM GType
gTypeSVGMetadataElement :: JSM GType
gTypeSVGMetadataElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGMetadataElement"

-- | Functions for this inteface are in "JSDOM.SVGMissingGlyphElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGMissingGlyphElement Mozilla SVGMissingGlyphElement documentation>
newtype SVGMissingGlyphElement = SVGMissingGlyphElement { SVGMissingGlyphElement -> JSVal
unSVGMissingGlyphElement :: JSVal }

instance PToJSVal SVGMissingGlyphElement where
  pToJSVal :: SVGMissingGlyphElement -> JSVal
pToJSVal = SVGMissingGlyphElement -> JSVal
unSVGMissingGlyphElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGMissingGlyphElement where
  pFromJSVal :: JSVal -> SVGMissingGlyphElement
pFromJSVal = JSVal -> SVGMissingGlyphElement
SVGMissingGlyphElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGMissingGlyphElement where
  toJSVal :: SVGMissingGlyphElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGMissingGlyphElement -> JSVal)
-> SVGMissingGlyphElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMissingGlyphElement -> JSVal
unSVGMissingGlyphElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGMissingGlyphElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGMissingGlyphElement)
fromJSVal JSVal
v = (JSVal -> SVGMissingGlyphElement)
-> Maybe JSVal -> Maybe SVGMissingGlyphElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGMissingGlyphElement
SVGMissingGlyphElement (Maybe JSVal -> Maybe SVGMissingGlyphElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGMissingGlyphElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGMissingGlyphElement
fromJSValUnchecked = SVGMissingGlyphElement -> JSM SVGMissingGlyphElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGMissingGlyphElement -> JSM SVGMissingGlyphElement)
-> (JSVal -> SVGMissingGlyphElement)
-> JSVal
-> JSM SVGMissingGlyphElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGMissingGlyphElement
SVGMissingGlyphElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGMissingGlyphElement where
  makeObject :: SVGMissingGlyphElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGMissingGlyphElement -> JSVal)
-> SVGMissingGlyphElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGMissingGlyphElement -> JSVal
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 :: SVGMissingGlyphElement -> JSM GType
typeGType SVGMissingGlyphElement
_ = JSM GType
gTypeSVGMissingGlyphElement
  {-# INLINE typeGType #-}

noSVGMissingGlyphElement :: Maybe SVGMissingGlyphElement
noSVGMissingGlyphElement :: Maybe SVGMissingGlyphElement
noSVGMissingGlyphElement = Maybe SVGMissingGlyphElement
forall a. Maybe a
Nothing
{-# INLINE noSVGMissingGlyphElement #-}

gTypeSVGMissingGlyphElement :: JSM GType
gTypeSVGMissingGlyphElement :: JSM GType
gTypeSVGMissingGlyphElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGMissingGlyphElement"

-- | Functions for this inteface are in "JSDOM.SVGNumber".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGNumber Mozilla SVGNumber documentation>
newtype SVGNumber = SVGNumber { SVGNumber -> JSVal
unSVGNumber :: JSVal }

instance PToJSVal SVGNumber where
  pToJSVal :: SVGNumber -> JSVal
pToJSVal = SVGNumber -> JSVal
unSVGNumber
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGNumber where
  pFromJSVal :: JSVal -> SVGNumber
pFromJSVal = JSVal -> SVGNumber
SVGNumber
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGNumber where
  toJSVal :: SVGNumber -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGNumber -> JSVal) -> SVGNumber -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGNumber -> JSVal
unSVGNumber
  {-# INLINE toJSVal #-}

instance FromJSVal SVGNumber where
  fromJSVal :: JSVal -> JSM (Maybe SVGNumber)
fromJSVal JSVal
v = (JSVal -> SVGNumber) -> Maybe JSVal -> Maybe SVGNumber
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGNumber
SVGNumber (Maybe JSVal -> Maybe SVGNumber)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGNumber)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGNumber
fromJSValUnchecked = SVGNumber -> JSM SVGNumber
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGNumber -> JSM SVGNumber)
-> (JSVal -> SVGNumber) -> JSVal -> JSM SVGNumber
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGNumber
SVGNumber
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGNumber where
  makeObject :: SVGNumber -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGNumber -> JSVal) -> SVGNumber -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGNumber -> JSVal
unSVGNumber

instance IsGObject SVGNumber where
  typeGType :: SVGNumber -> JSM GType
typeGType SVGNumber
_ = JSM GType
gTypeSVGNumber
  {-# INLINE typeGType #-}

noSVGNumber :: Maybe SVGNumber
noSVGNumber :: Maybe SVGNumber
noSVGNumber = Maybe SVGNumber
forall a. Maybe a
Nothing
{-# INLINE noSVGNumber #-}

gTypeSVGNumber :: JSM GType
gTypeSVGNumber :: JSM GType
gTypeSVGNumber = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGNumber"

-- | Functions for this inteface are in "JSDOM.SVGNumberList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGNumberList Mozilla SVGNumberList documentation>
newtype SVGNumberList = SVGNumberList { SVGNumberList -> JSVal
unSVGNumberList :: JSVal }

instance PToJSVal SVGNumberList where
  pToJSVal :: SVGNumberList -> JSVal
pToJSVal = SVGNumberList -> JSVal
unSVGNumberList
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGNumberList where
  pFromJSVal :: JSVal -> SVGNumberList
pFromJSVal = JSVal -> SVGNumberList
SVGNumberList
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGNumberList where
  toJSVal :: SVGNumberList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGNumberList -> JSVal) -> SVGNumberList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGNumberList -> JSVal
unSVGNumberList
  {-# INLINE toJSVal #-}

instance FromJSVal SVGNumberList where
  fromJSVal :: JSVal -> JSM (Maybe SVGNumberList)
fromJSVal JSVal
v = (JSVal -> SVGNumberList) -> Maybe JSVal -> Maybe SVGNumberList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGNumberList
SVGNumberList (Maybe JSVal -> Maybe SVGNumberList)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGNumberList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGNumberList
fromJSValUnchecked = SVGNumberList -> JSM SVGNumberList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGNumberList -> JSM SVGNumberList)
-> (JSVal -> SVGNumberList) -> JSVal -> JSM SVGNumberList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGNumberList
SVGNumberList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGNumberList where
  makeObject :: SVGNumberList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGNumberList -> JSVal) -> SVGNumberList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGNumberList -> JSVal
unSVGNumberList

instance IsGObject SVGNumberList where
  typeGType :: SVGNumberList -> JSM GType
typeGType SVGNumberList
_ = JSM GType
gTypeSVGNumberList
  {-# INLINE typeGType #-}

noSVGNumberList :: Maybe SVGNumberList
noSVGNumberList :: Maybe SVGNumberList
noSVGNumberList = Maybe SVGNumberList
forall a. Maybe a
Nothing
{-# INLINE noSVGNumberList #-}

gTypeSVGNumberList :: JSM GType
gTypeSVGNumberList :: JSM GType
gTypeSVGNumberList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGNumberList"

-- | Functions for this inteface are in "JSDOM.SVGPathElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathElement Mozilla SVGPathElement documentation>
newtype SVGPathElement = SVGPathElement { SVGPathElement -> JSVal
unSVGPathElement :: JSVal }

instance PToJSVal SVGPathElement where
  pToJSVal :: SVGPathElement -> JSVal
pToJSVal = SVGPathElement -> JSVal
unSVGPathElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathElement where
  pFromJSVal :: JSVal -> SVGPathElement
pFromJSVal = JSVal -> SVGPathElement
SVGPathElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathElement where
  toJSVal :: SVGPathElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathElement -> JSVal) -> SVGPathElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathElement -> JSVal
unSVGPathElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathElement)
fromJSVal JSVal
v = (JSVal -> SVGPathElement) -> Maybe JSVal -> Maybe SVGPathElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathElement
SVGPathElement (Maybe JSVal -> Maybe SVGPathElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathElement
fromJSValUnchecked = SVGPathElement -> JSM SVGPathElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathElement -> JSM SVGPathElement)
-> (JSVal -> SVGPathElement) -> JSVal -> JSM SVGPathElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathElement
SVGPathElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathElement where
  makeObject :: SVGPathElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathElement -> JSVal) -> SVGPathElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathElement -> JSVal
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 :: SVGPathElement -> JSM GType
typeGType SVGPathElement
_ = JSM GType
gTypeSVGPathElement
  {-# INLINE typeGType #-}

noSVGPathElement :: Maybe SVGPathElement
noSVGPathElement :: Maybe SVGPathElement
noSVGPathElement = Maybe SVGPathElement
forall a. Maybe a
Nothing
{-# INLINE noSVGPathElement #-}

gTypeSVGPathElement :: JSM GType
gTypeSVGPathElement :: JSM GType
gTypeSVGPathElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathElement"

-- | Functions for this inteface are in "JSDOM.SVGPathSeg".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSeg Mozilla SVGPathSeg documentation>
newtype SVGPathSeg = SVGPathSeg { SVGPathSeg -> JSVal
unSVGPathSeg :: JSVal }

instance PToJSVal SVGPathSeg where
  pToJSVal :: SVGPathSeg -> JSVal
pToJSVal = SVGPathSeg -> JSVal
unSVGPathSeg
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSeg where
  pFromJSVal :: JSVal -> SVGPathSeg
pFromJSVal = JSVal -> SVGPathSeg
SVGPathSeg
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSeg where
  toJSVal :: SVGPathSeg -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSeg -> JSVal) -> SVGPathSeg -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSeg -> JSVal
unSVGPathSeg
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSeg where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSeg)
fromJSVal JSVal
v = (JSVal -> SVGPathSeg) -> Maybe JSVal -> Maybe SVGPathSeg
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSeg
SVGPathSeg (Maybe JSVal -> Maybe SVGPathSeg)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSeg)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSeg
fromJSValUnchecked = SVGPathSeg -> JSM SVGPathSeg
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSeg -> JSM SVGPathSeg)
-> (JSVal -> SVGPathSeg) -> JSVal -> JSM SVGPathSeg
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSeg
SVGPathSeg
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSeg where
  makeObject :: SVGPathSeg -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSeg -> JSVal) -> SVGPathSeg -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSeg -> JSVal
unSVGPathSeg

class (IsGObject o) => IsSVGPathSeg o
toSVGPathSeg :: IsSVGPathSeg o => o -> SVGPathSeg
toSVGPathSeg :: forall o. IsSVGPathSeg o => o -> SVGPathSeg
toSVGPathSeg = JSVal -> SVGPathSeg
SVGPathSeg (JSVal -> SVGPathSeg) -> (o -> JSVal) -> o -> SVGPathSeg
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsSVGPathSeg SVGPathSeg
instance IsGObject SVGPathSeg where
  typeGType :: SVGPathSeg -> JSM GType
typeGType SVGPathSeg
_ = JSM GType
gTypeSVGPathSeg
  {-# INLINE typeGType #-}

noSVGPathSeg :: Maybe SVGPathSeg
noSVGPathSeg :: Maybe SVGPathSeg
noSVGPathSeg = Maybe SVGPathSeg
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSeg #-}

gTypeSVGPathSeg :: JSM GType
gTypeSVGPathSeg :: JSM GType
gTypeSVGPathSeg = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSeg"

-- | Functions for this inteface are in "JSDOM.SVGPathSegArcAbs".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegArcAbs Mozilla SVGPathSegArcAbs documentation>
newtype SVGPathSegArcAbs = SVGPathSegArcAbs { SVGPathSegArcAbs -> JSVal
unSVGPathSegArcAbs :: JSVal }

instance PToJSVal SVGPathSegArcAbs where
  pToJSVal :: SVGPathSegArcAbs -> JSVal
pToJSVal = SVGPathSegArcAbs -> JSVal
unSVGPathSegArcAbs
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegArcAbs where
  pFromJSVal :: JSVal -> SVGPathSegArcAbs
pFromJSVal = JSVal -> SVGPathSegArcAbs
SVGPathSegArcAbs
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegArcAbs where
  toJSVal :: SVGPathSegArcAbs -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegArcAbs -> JSVal) -> SVGPathSegArcAbs -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegArcAbs -> JSVal
unSVGPathSegArcAbs
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegArcAbs where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegArcAbs)
fromJSVal JSVal
v = (JSVal -> SVGPathSegArcAbs)
-> Maybe JSVal -> Maybe SVGPathSegArcAbs
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegArcAbs
SVGPathSegArcAbs (Maybe JSVal -> Maybe SVGPathSegArcAbs)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegArcAbs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegArcAbs
fromJSValUnchecked = SVGPathSegArcAbs -> JSM SVGPathSegArcAbs
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegArcAbs -> JSM SVGPathSegArcAbs)
-> (JSVal -> SVGPathSegArcAbs) -> JSVal -> JSM SVGPathSegArcAbs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegArcAbs
SVGPathSegArcAbs
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegArcAbs where
  makeObject :: SVGPathSegArcAbs -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegArcAbs -> JSVal) -> SVGPathSegArcAbs -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegArcAbs -> JSVal
unSVGPathSegArcAbs

instance IsSVGPathSeg SVGPathSegArcAbs
instance IsGObject SVGPathSegArcAbs where
  typeGType :: SVGPathSegArcAbs -> JSM GType
typeGType SVGPathSegArcAbs
_ = JSM GType
gTypeSVGPathSegArcAbs
  {-# INLINE typeGType #-}

noSVGPathSegArcAbs :: Maybe SVGPathSegArcAbs
noSVGPathSegArcAbs :: Maybe SVGPathSegArcAbs
noSVGPathSegArcAbs = Maybe SVGPathSegArcAbs
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegArcAbs #-}

gTypeSVGPathSegArcAbs :: JSM GType
gTypeSVGPathSegArcAbs :: JSM GType
gTypeSVGPathSegArcAbs = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegArcAbs"

-- | Functions for this inteface are in "JSDOM.SVGPathSegArcRel".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegArcRel Mozilla SVGPathSegArcRel documentation>
newtype SVGPathSegArcRel = SVGPathSegArcRel { SVGPathSegArcRel -> JSVal
unSVGPathSegArcRel :: JSVal }

instance PToJSVal SVGPathSegArcRel where
  pToJSVal :: SVGPathSegArcRel -> JSVal
pToJSVal = SVGPathSegArcRel -> JSVal
unSVGPathSegArcRel
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegArcRel where
  pFromJSVal :: JSVal -> SVGPathSegArcRel
pFromJSVal = JSVal -> SVGPathSegArcRel
SVGPathSegArcRel
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegArcRel where
  toJSVal :: SVGPathSegArcRel -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegArcRel -> JSVal) -> SVGPathSegArcRel -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegArcRel -> JSVal
unSVGPathSegArcRel
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegArcRel where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegArcRel)
fromJSVal JSVal
v = (JSVal -> SVGPathSegArcRel)
-> Maybe JSVal -> Maybe SVGPathSegArcRel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegArcRel
SVGPathSegArcRel (Maybe JSVal -> Maybe SVGPathSegArcRel)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegArcRel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegArcRel
fromJSValUnchecked = SVGPathSegArcRel -> JSM SVGPathSegArcRel
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegArcRel -> JSM SVGPathSegArcRel)
-> (JSVal -> SVGPathSegArcRel) -> JSVal -> JSM SVGPathSegArcRel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegArcRel
SVGPathSegArcRel
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegArcRel where
  makeObject :: SVGPathSegArcRel -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegArcRel -> JSVal) -> SVGPathSegArcRel -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegArcRel -> JSVal
unSVGPathSegArcRel

instance IsSVGPathSeg SVGPathSegArcRel
instance IsGObject SVGPathSegArcRel where
  typeGType :: SVGPathSegArcRel -> JSM GType
typeGType SVGPathSegArcRel
_ = JSM GType
gTypeSVGPathSegArcRel
  {-# INLINE typeGType #-}

noSVGPathSegArcRel :: Maybe SVGPathSegArcRel
noSVGPathSegArcRel :: Maybe SVGPathSegArcRel
noSVGPathSegArcRel = Maybe SVGPathSegArcRel
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegArcRel #-}

gTypeSVGPathSegArcRel :: JSM GType
gTypeSVGPathSegArcRel :: JSM GType
gTypeSVGPathSegArcRel = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegArcRel"

-- | Functions for this inteface are in "JSDOM.SVGPathSegClosePath".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegClosePath Mozilla SVGPathSegClosePath documentation>
newtype SVGPathSegClosePath = SVGPathSegClosePath { SVGPathSegClosePath -> JSVal
unSVGPathSegClosePath :: JSVal }

instance PToJSVal SVGPathSegClosePath where
  pToJSVal :: SVGPathSegClosePath -> JSVal
pToJSVal = SVGPathSegClosePath -> JSVal
unSVGPathSegClosePath
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegClosePath where
  pFromJSVal :: JSVal -> SVGPathSegClosePath
pFromJSVal = JSVal -> SVGPathSegClosePath
SVGPathSegClosePath
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegClosePath where
  toJSVal :: SVGPathSegClosePath -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegClosePath -> JSVal)
-> SVGPathSegClosePath
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegClosePath -> JSVal
unSVGPathSegClosePath
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegClosePath where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegClosePath)
fromJSVal JSVal
v = (JSVal -> SVGPathSegClosePath)
-> Maybe JSVal -> Maybe SVGPathSegClosePath
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegClosePath
SVGPathSegClosePath (Maybe JSVal -> Maybe SVGPathSegClosePath)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegClosePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegClosePath
fromJSValUnchecked = SVGPathSegClosePath -> JSM SVGPathSegClosePath
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegClosePath -> JSM SVGPathSegClosePath)
-> (JSVal -> SVGPathSegClosePath)
-> JSVal
-> JSM SVGPathSegClosePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegClosePath
SVGPathSegClosePath
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegClosePath where
  makeObject :: SVGPathSegClosePath -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegClosePath -> JSVal)
-> SVGPathSegClosePath
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegClosePath -> JSVal
unSVGPathSegClosePath

instance IsSVGPathSeg SVGPathSegClosePath
instance IsGObject SVGPathSegClosePath where
  typeGType :: SVGPathSegClosePath -> JSM GType
typeGType SVGPathSegClosePath
_ = JSM GType
gTypeSVGPathSegClosePath
  {-# INLINE typeGType #-}

noSVGPathSegClosePath :: Maybe SVGPathSegClosePath
noSVGPathSegClosePath :: Maybe SVGPathSegClosePath
noSVGPathSegClosePath = Maybe SVGPathSegClosePath
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegClosePath #-}

gTypeSVGPathSegClosePath :: JSM GType
gTypeSVGPathSegClosePath :: JSM GType
gTypeSVGPathSegClosePath = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegClosePath"

-- | Functions for this inteface are in "JSDOM.SVGPathSegCurvetoCubicAbs".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegCurvetoCubicAbs Mozilla SVGPathSegCurvetoCubicAbs documentation>
newtype SVGPathSegCurvetoCubicAbs = SVGPathSegCurvetoCubicAbs { SVGPathSegCurvetoCubicAbs -> JSVal
unSVGPathSegCurvetoCubicAbs :: JSVal }

instance PToJSVal SVGPathSegCurvetoCubicAbs where
  pToJSVal :: SVGPathSegCurvetoCubicAbs -> JSVal
pToJSVal = SVGPathSegCurvetoCubicAbs -> JSVal
unSVGPathSegCurvetoCubicAbs
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegCurvetoCubicAbs where
  pFromJSVal :: JSVal -> SVGPathSegCurvetoCubicAbs
pFromJSVal = JSVal -> SVGPathSegCurvetoCubicAbs
SVGPathSegCurvetoCubicAbs
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegCurvetoCubicAbs where
  toJSVal :: SVGPathSegCurvetoCubicAbs -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegCurvetoCubicAbs -> JSVal)
-> SVGPathSegCurvetoCubicAbs
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoCubicAbs -> JSVal
unSVGPathSegCurvetoCubicAbs
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegCurvetoCubicAbs where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegCurvetoCubicAbs)
fromJSVal JSVal
v = (JSVal -> SVGPathSegCurvetoCubicAbs)
-> Maybe JSVal -> Maybe SVGPathSegCurvetoCubicAbs
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegCurvetoCubicAbs
SVGPathSegCurvetoCubicAbs (Maybe JSVal -> Maybe SVGPathSegCurvetoCubicAbs)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegCurvetoCubicAbs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegCurvetoCubicAbs
fromJSValUnchecked = SVGPathSegCurvetoCubicAbs -> JSM SVGPathSegCurvetoCubicAbs
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegCurvetoCubicAbs -> JSM SVGPathSegCurvetoCubicAbs)
-> (JSVal -> SVGPathSegCurvetoCubicAbs)
-> JSVal
-> JSM SVGPathSegCurvetoCubicAbs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegCurvetoCubicAbs
SVGPathSegCurvetoCubicAbs
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegCurvetoCubicAbs where
  makeObject :: SVGPathSegCurvetoCubicAbs -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegCurvetoCubicAbs -> JSVal)
-> SVGPathSegCurvetoCubicAbs
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoCubicAbs -> JSVal
unSVGPathSegCurvetoCubicAbs

instance IsSVGPathSeg SVGPathSegCurvetoCubicAbs
instance IsGObject SVGPathSegCurvetoCubicAbs where
  typeGType :: SVGPathSegCurvetoCubicAbs -> JSM GType
typeGType SVGPathSegCurvetoCubicAbs
_ = JSM GType
gTypeSVGPathSegCurvetoCubicAbs
  {-# INLINE typeGType #-}

noSVGPathSegCurvetoCubicAbs :: Maybe SVGPathSegCurvetoCubicAbs
noSVGPathSegCurvetoCubicAbs :: Maybe SVGPathSegCurvetoCubicAbs
noSVGPathSegCurvetoCubicAbs = Maybe SVGPathSegCurvetoCubicAbs
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegCurvetoCubicAbs #-}

gTypeSVGPathSegCurvetoCubicAbs :: JSM GType
gTypeSVGPathSegCurvetoCubicAbs :: JSM GType
gTypeSVGPathSegCurvetoCubicAbs = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegCurvetoCubicAbs"

-- | Functions for this inteface are in "JSDOM.SVGPathSegCurvetoCubicRel".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegCurvetoCubicRel Mozilla SVGPathSegCurvetoCubicRel documentation>
newtype SVGPathSegCurvetoCubicRel = SVGPathSegCurvetoCubicRel { SVGPathSegCurvetoCubicRel -> JSVal
unSVGPathSegCurvetoCubicRel :: JSVal }

instance PToJSVal SVGPathSegCurvetoCubicRel where
  pToJSVal :: SVGPathSegCurvetoCubicRel -> JSVal
pToJSVal = SVGPathSegCurvetoCubicRel -> JSVal
unSVGPathSegCurvetoCubicRel
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegCurvetoCubicRel where
  pFromJSVal :: JSVal -> SVGPathSegCurvetoCubicRel
pFromJSVal = JSVal -> SVGPathSegCurvetoCubicRel
SVGPathSegCurvetoCubicRel
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegCurvetoCubicRel where
  toJSVal :: SVGPathSegCurvetoCubicRel -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegCurvetoCubicRel -> JSVal)
-> SVGPathSegCurvetoCubicRel
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoCubicRel -> JSVal
unSVGPathSegCurvetoCubicRel
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegCurvetoCubicRel where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegCurvetoCubicRel)
fromJSVal JSVal
v = (JSVal -> SVGPathSegCurvetoCubicRel)
-> Maybe JSVal -> Maybe SVGPathSegCurvetoCubicRel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegCurvetoCubicRel
SVGPathSegCurvetoCubicRel (Maybe JSVal -> Maybe SVGPathSegCurvetoCubicRel)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegCurvetoCubicRel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegCurvetoCubicRel
fromJSValUnchecked = SVGPathSegCurvetoCubicRel -> JSM SVGPathSegCurvetoCubicRel
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegCurvetoCubicRel -> JSM SVGPathSegCurvetoCubicRel)
-> (JSVal -> SVGPathSegCurvetoCubicRel)
-> JSVal
-> JSM SVGPathSegCurvetoCubicRel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegCurvetoCubicRel
SVGPathSegCurvetoCubicRel
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegCurvetoCubicRel where
  makeObject :: SVGPathSegCurvetoCubicRel -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegCurvetoCubicRel -> JSVal)
-> SVGPathSegCurvetoCubicRel
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoCubicRel -> JSVal
unSVGPathSegCurvetoCubicRel

instance IsSVGPathSeg SVGPathSegCurvetoCubicRel
instance IsGObject SVGPathSegCurvetoCubicRel where
  typeGType :: SVGPathSegCurvetoCubicRel -> JSM GType
typeGType SVGPathSegCurvetoCubicRel
_ = JSM GType
gTypeSVGPathSegCurvetoCubicRel
  {-# INLINE typeGType #-}

noSVGPathSegCurvetoCubicRel :: Maybe SVGPathSegCurvetoCubicRel
noSVGPathSegCurvetoCubicRel :: Maybe SVGPathSegCurvetoCubicRel
noSVGPathSegCurvetoCubicRel = Maybe SVGPathSegCurvetoCubicRel
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegCurvetoCubicRel #-}

gTypeSVGPathSegCurvetoCubicRel :: JSM GType
gTypeSVGPathSegCurvetoCubicRel :: JSM GType
gTypeSVGPathSegCurvetoCubicRel = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegCurvetoCubicRel"

-- | Functions for this inteface are in "JSDOM.SVGPathSegCurvetoCubicSmoothAbs".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegCurvetoCubicSmoothAbs Mozilla SVGPathSegCurvetoCubicSmoothAbs documentation>
newtype SVGPathSegCurvetoCubicSmoothAbs = SVGPathSegCurvetoCubicSmoothAbs { SVGPathSegCurvetoCubicSmoothAbs -> JSVal
unSVGPathSegCurvetoCubicSmoothAbs :: JSVal }

instance PToJSVal SVGPathSegCurvetoCubicSmoothAbs where
  pToJSVal :: SVGPathSegCurvetoCubicSmoothAbs -> JSVal
pToJSVal = SVGPathSegCurvetoCubicSmoothAbs -> JSVal
unSVGPathSegCurvetoCubicSmoothAbs
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegCurvetoCubicSmoothAbs where
  pFromJSVal :: JSVal -> SVGPathSegCurvetoCubicSmoothAbs
pFromJSVal = JSVal -> SVGPathSegCurvetoCubicSmoothAbs
SVGPathSegCurvetoCubicSmoothAbs
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegCurvetoCubicSmoothAbs where
  toJSVal :: SVGPathSegCurvetoCubicSmoothAbs -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegCurvetoCubicSmoothAbs -> JSVal)
-> SVGPathSegCurvetoCubicSmoothAbs
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoCubicSmoothAbs -> JSVal
unSVGPathSegCurvetoCubicSmoothAbs
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegCurvetoCubicSmoothAbs where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegCurvetoCubicSmoothAbs)
fromJSVal JSVal
v = (JSVal -> SVGPathSegCurvetoCubicSmoothAbs)
-> Maybe JSVal -> Maybe SVGPathSegCurvetoCubicSmoothAbs
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegCurvetoCubicSmoothAbs
SVGPathSegCurvetoCubicSmoothAbs (Maybe JSVal -> Maybe SVGPathSegCurvetoCubicSmoothAbs)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegCurvetoCubicSmoothAbs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegCurvetoCubicSmoothAbs
fromJSValUnchecked = SVGPathSegCurvetoCubicSmoothAbs
-> JSM SVGPathSegCurvetoCubicSmoothAbs
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegCurvetoCubicSmoothAbs
 -> JSM SVGPathSegCurvetoCubicSmoothAbs)
-> (JSVal -> SVGPathSegCurvetoCubicSmoothAbs)
-> JSVal
-> JSM SVGPathSegCurvetoCubicSmoothAbs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegCurvetoCubicSmoothAbs
SVGPathSegCurvetoCubicSmoothAbs
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegCurvetoCubicSmoothAbs where
  makeObject :: SVGPathSegCurvetoCubicSmoothAbs -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegCurvetoCubicSmoothAbs -> JSVal)
-> SVGPathSegCurvetoCubicSmoothAbs
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoCubicSmoothAbs -> JSVal
unSVGPathSegCurvetoCubicSmoothAbs

instance IsSVGPathSeg SVGPathSegCurvetoCubicSmoothAbs
instance IsGObject SVGPathSegCurvetoCubicSmoothAbs where
  typeGType :: SVGPathSegCurvetoCubicSmoothAbs -> JSM GType
typeGType SVGPathSegCurvetoCubicSmoothAbs
_ = JSM GType
gTypeSVGPathSegCurvetoCubicSmoothAbs
  {-# INLINE typeGType #-}

noSVGPathSegCurvetoCubicSmoothAbs :: Maybe SVGPathSegCurvetoCubicSmoothAbs
noSVGPathSegCurvetoCubicSmoothAbs :: Maybe SVGPathSegCurvetoCubicSmoothAbs
noSVGPathSegCurvetoCubicSmoothAbs = Maybe SVGPathSegCurvetoCubicSmoothAbs
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegCurvetoCubicSmoothAbs #-}

gTypeSVGPathSegCurvetoCubicSmoothAbs :: JSM GType
gTypeSVGPathSegCurvetoCubicSmoothAbs :: JSM GType
gTypeSVGPathSegCurvetoCubicSmoothAbs = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegCurvetoCubicSmoothAbs"

-- | Functions for this inteface are in "JSDOM.SVGPathSegCurvetoCubicSmoothRel".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegCurvetoCubicSmoothRel Mozilla SVGPathSegCurvetoCubicSmoothRel documentation>
newtype SVGPathSegCurvetoCubicSmoothRel = SVGPathSegCurvetoCubicSmoothRel { SVGPathSegCurvetoCubicSmoothRel -> JSVal
unSVGPathSegCurvetoCubicSmoothRel :: JSVal }

instance PToJSVal SVGPathSegCurvetoCubicSmoothRel where
  pToJSVal :: SVGPathSegCurvetoCubicSmoothRel -> JSVal
pToJSVal = SVGPathSegCurvetoCubicSmoothRel -> JSVal
unSVGPathSegCurvetoCubicSmoothRel
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegCurvetoCubicSmoothRel where
  pFromJSVal :: JSVal -> SVGPathSegCurvetoCubicSmoothRel
pFromJSVal = JSVal -> SVGPathSegCurvetoCubicSmoothRel
SVGPathSegCurvetoCubicSmoothRel
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegCurvetoCubicSmoothRel where
  toJSVal :: SVGPathSegCurvetoCubicSmoothRel -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegCurvetoCubicSmoothRel -> JSVal)
-> SVGPathSegCurvetoCubicSmoothRel
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoCubicSmoothRel -> JSVal
unSVGPathSegCurvetoCubicSmoothRel
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegCurvetoCubicSmoothRel where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegCurvetoCubicSmoothRel)
fromJSVal JSVal
v = (JSVal -> SVGPathSegCurvetoCubicSmoothRel)
-> Maybe JSVal -> Maybe SVGPathSegCurvetoCubicSmoothRel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegCurvetoCubicSmoothRel
SVGPathSegCurvetoCubicSmoothRel (Maybe JSVal -> Maybe SVGPathSegCurvetoCubicSmoothRel)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegCurvetoCubicSmoothRel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegCurvetoCubicSmoothRel
fromJSValUnchecked = SVGPathSegCurvetoCubicSmoothRel
-> JSM SVGPathSegCurvetoCubicSmoothRel
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegCurvetoCubicSmoothRel
 -> JSM SVGPathSegCurvetoCubicSmoothRel)
-> (JSVal -> SVGPathSegCurvetoCubicSmoothRel)
-> JSVal
-> JSM SVGPathSegCurvetoCubicSmoothRel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegCurvetoCubicSmoothRel
SVGPathSegCurvetoCubicSmoothRel
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegCurvetoCubicSmoothRel where
  makeObject :: SVGPathSegCurvetoCubicSmoothRel -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegCurvetoCubicSmoothRel -> JSVal)
-> SVGPathSegCurvetoCubicSmoothRel
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoCubicSmoothRel -> JSVal
unSVGPathSegCurvetoCubicSmoothRel

instance IsSVGPathSeg SVGPathSegCurvetoCubicSmoothRel
instance IsGObject SVGPathSegCurvetoCubicSmoothRel where
  typeGType :: SVGPathSegCurvetoCubicSmoothRel -> JSM GType
typeGType SVGPathSegCurvetoCubicSmoothRel
_ = JSM GType
gTypeSVGPathSegCurvetoCubicSmoothRel
  {-# INLINE typeGType #-}

noSVGPathSegCurvetoCubicSmoothRel :: Maybe SVGPathSegCurvetoCubicSmoothRel
noSVGPathSegCurvetoCubicSmoothRel :: Maybe SVGPathSegCurvetoCubicSmoothRel
noSVGPathSegCurvetoCubicSmoothRel = Maybe SVGPathSegCurvetoCubicSmoothRel
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegCurvetoCubicSmoothRel #-}

gTypeSVGPathSegCurvetoCubicSmoothRel :: JSM GType
gTypeSVGPathSegCurvetoCubicSmoothRel :: JSM GType
gTypeSVGPathSegCurvetoCubicSmoothRel = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegCurvetoCubicSmoothRel"

-- | Functions for this inteface are in "JSDOM.SVGPathSegCurvetoQuadraticAbs".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegCurvetoQuadraticAbs Mozilla SVGPathSegCurvetoQuadraticAbs documentation>
newtype SVGPathSegCurvetoQuadraticAbs = SVGPathSegCurvetoQuadraticAbs { SVGPathSegCurvetoQuadraticAbs -> JSVal
unSVGPathSegCurvetoQuadraticAbs :: JSVal }

instance PToJSVal SVGPathSegCurvetoQuadraticAbs where
  pToJSVal :: SVGPathSegCurvetoQuadraticAbs -> JSVal
pToJSVal = SVGPathSegCurvetoQuadraticAbs -> JSVal
unSVGPathSegCurvetoQuadraticAbs
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegCurvetoQuadraticAbs where
  pFromJSVal :: JSVal -> SVGPathSegCurvetoQuadraticAbs
pFromJSVal = JSVal -> SVGPathSegCurvetoQuadraticAbs
SVGPathSegCurvetoQuadraticAbs
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegCurvetoQuadraticAbs where
  toJSVal :: SVGPathSegCurvetoQuadraticAbs -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegCurvetoQuadraticAbs -> JSVal)
-> SVGPathSegCurvetoQuadraticAbs
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoQuadraticAbs -> JSVal
unSVGPathSegCurvetoQuadraticAbs
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegCurvetoQuadraticAbs where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegCurvetoQuadraticAbs)
fromJSVal JSVal
v = (JSVal -> SVGPathSegCurvetoQuadraticAbs)
-> Maybe JSVal -> Maybe SVGPathSegCurvetoQuadraticAbs
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegCurvetoQuadraticAbs
SVGPathSegCurvetoQuadraticAbs (Maybe JSVal -> Maybe SVGPathSegCurvetoQuadraticAbs)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegCurvetoQuadraticAbs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegCurvetoQuadraticAbs
fromJSValUnchecked = SVGPathSegCurvetoQuadraticAbs -> JSM SVGPathSegCurvetoQuadraticAbs
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegCurvetoQuadraticAbs
 -> JSM SVGPathSegCurvetoQuadraticAbs)
-> (JSVal -> SVGPathSegCurvetoQuadraticAbs)
-> JSVal
-> JSM SVGPathSegCurvetoQuadraticAbs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegCurvetoQuadraticAbs
SVGPathSegCurvetoQuadraticAbs
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegCurvetoQuadraticAbs where
  makeObject :: SVGPathSegCurvetoQuadraticAbs -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegCurvetoQuadraticAbs -> JSVal)
-> SVGPathSegCurvetoQuadraticAbs
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoQuadraticAbs -> JSVal
unSVGPathSegCurvetoQuadraticAbs

instance IsSVGPathSeg SVGPathSegCurvetoQuadraticAbs
instance IsGObject SVGPathSegCurvetoQuadraticAbs where
  typeGType :: SVGPathSegCurvetoQuadraticAbs -> JSM GType
typeGType SVGPathSegCurvetoQuadraticAbs
_ = JSM GType
gTypeSVGPathSegCurvetoQuadraticAbs
  {-# INLINE typeGType #-}

noSVGPathSegCurvetoQuadraticAbs :: Maybe SVGPathSegCurvetoQuadraticAbs
noSVGPathSegCurvetoQuadraticAbs :: Maybe SVGPathSegCurvetoQuadraticAbs
noSVGPathSegCurvetoQuadraticAbs = Maybe SVGPathSegCurvetoQuadraticAbs
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegCurvetoQuadraticAbs #-}

gTypeSVGPathSegCurvetoQuadraticAbs :: JSM GType
gTypeSVGPathSegCurvetoQuadraticAbs :: JSM GType
gTypeSVGPathSegCurvetoQuadraticAbs = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegCurvetoQuadraticAbs"

-- | Functions for this inteface are in "JSDOM.SVGPathSegCurvetoQuadraticRel".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegCurvetoQuadraticRel Mozilla SVGPathSegCurvetoQuadraticRel documentation>
newtype SVGPathSegCurvetoQuadraticRel = SVGPathSegCurvetoQuadraticRel { SVGPathSegCurvetoQuadraticRel -> JSVal
unSVGPathSegCurvetoQuadraticRel :: JSVal }

instance PToJSVal SVGPathSegCurvetoQuadraticRel where
  pToJSVal :: SVGPathSegCurvetoQuadraticRel -> JSVal
pToJSVal = SVGPathSegCurvetoQuadraticRel -> JSVal
unSVGPathSegCurvetoQuadraticRel
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegCurvetoQuadraticRel where
  pFromJSVal :: JSVal -> SVGPathSegCurvetoQuadraticRel
pFromJSVal = JSVal -> SVGPathSegCurvetoQuadraticRel
SVGPathSegCurvetoQuadraticRel
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegCurvetoQuadraticRel where
  toJSVal :: SVGPathSegCurvetoQuadraticRel -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegCurvetoQuadraticRel -> JSVal)
-> SVGPathSegCurvetoQuadraticRel
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoQuadraticRel -> JSVal
unSVGPathSegCurvetoQuadraticRel
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegCurvetoQuadraticRel where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegCurvetoQuadraticRel)
fromJSVal JSVal
v = (JSVal -> SVGPathSegCurvetoQuadraticRel)
-> Maybe JSVal -> Maybe SVGPathSegCurvetoQuadraticRel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegCurvetoQuadraticRel
SVGPathSegCurvetoQuadraticRel (Maybe JSVal -> Maybe SVGPathSegCurvetoQuadraticRel)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegCurvetoQuadraticRel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegCurvetoQuadraticRel
fromJSValUnchecked = SVGPathSegCurvetoQuadraticRel -> JSM SVGPathSegCurvetoQuadraticRel
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegCurvetoQuadraticRel
 -> JSM SVGPathSegCurvetoQuadraticRel)
-> (JSVal -> SVGPathSegCurvetoQuadraticRel)
-> JSVal
-> JSM SVGPathSegCurvetoQuadraticRel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegCurvetoQuadraticRel
SVGPathSegCurvetoQuadraticRel
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegCurvetoQuadraticRel where
  makeObject :: SVGPathSegCurvetoQuadraticRel -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegCurvetoQuadraticRel -> JSVal)
-> SVGPathSegCurvetoQuadraticRel
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoQuadraticRel -> JSVal
unSVGPathSegCurvetoQuadraticRel

instance IsSVGPathSeg SVGPathSegCurvetoQuadraticRel
instance IsGObject SVGPathSegCurvetoQuadraticRel where
  typeGType :: SVGPathSegCurvetoQuadraticRel -> JSM GType
typeGType SVGPathSegCurvetoQuadraticRel
_ = JSM GType
gTypeSVGPathSegCurvetoQuadraticRel
  {-# INLINE typeGType #-}

noSVGPathSegCurvetoQuadraticRel :: Maybe SVGPathSegCurvetoQuadraticRel
noSVGPathSegCurvetoQuadraticRel :: Maybe SVGPathSegCurvetoQuadraticRel
noSVGPathSegCurvetoQuadraticRel = Maybe SVGPathSegCurvetoQuadraticRel
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegCurvetoQuadraticRel #-}

gTypeSVGPathSegCurvetoQuadraticRel :: JSM GType
gTypeSVGPathSegCurvetoQuadraticRel :: JSM GType
gTypeSVGPathSegCurvetoQuadraticRel = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegCurvetoQuadraticRel"

-- | Functions for this inteface are in "JSDOM.SVGPathSegCurvetoQuadraticSmoothAbs".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegCurvetoQuadraticSmoothAbs Mozilla SVGPathSegCurvetoQuadraticSmoothAbs documentation>
newtype SVGPathSegCurvetoQuadraticSmoothAbs = SVGPathSegCurvetoQuadraticSmoothAbs { SVGPathSegCurvetoQuadraticSmoothAbs -> JSVal
unSVGPathSegCurvetoQuadraticSmoothAbs :: JSVal }

instance PToJSVal SVGPathSegCurvetoQuadraticSmoothAbs where
  pToJSVal :: SVGPathSegCurvetoQuadraticSmoothAbs -> JSVal
pToJSVal = SVGPathSegCurvetoQuadraticSmoothAbs -> JSVal
unSVGPathSegCurvetoQuadraticSmoothAbs
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegCurvetoQuadraticSmoothAbs where
  pFromJSVal :: JSVal -> SVGPathSegCurvetoQuadraticSmoothAbs
pFromJSVal = JSVal -> SVGPathSegCurvetoQuadraticSmoothAbs
SVGPathSegCurvetoQuadraticSmoothAbs
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegCurvetoQuadraticSmoothAbs where
  toJSVal :: SVGPathSegCurvetoQuadraticSmoothAbs -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegCurvetoQuadraticSmoothAbs -> JSVal)
-> SVGPathSegCurvetoQuadraticSmoothAbs
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoQuadraticSmoothAbs -> JSVal
unSVGPathSegCurvetoQuadraticSmoothAbs
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegCurvetoQuadraticSmoothAbs where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegCurvetoQuadraticSmoothAbs)
fromJSVal JSVal
v = (JSVal -> SVGPathSegCurvetoQuadraticSmoothAbs)
-> Maybe JSVal -> Maybe SVGPathSegCurvetoQuadraticSmoothAbs
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegCurvetoQuadraticSmoothAbs
SVGPathSegCurvetoQuadraticSmoothAbs (Maybe JSVal -> Maybe SVGPathSegCurvetoQuadraticSmoothAbs)
-> JSM (Maybe JSVal)
-> JSM (Maybe SVGPathSegCurvetoQuadraticSmoothAbs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegCurvetoQuadraticSmoothAbs
fromJSValUnchecked = SVGPathSegCurvetoQuadraticSmoothAbs
-> JSM SVGPathSegCurvetoQuadraticSmoothAbs
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegCurvetoQuadraticSmoothAbs
 -> JSM SVGPathSegCurvetoQuadraticSmoothAbs)
-> (JSVal -> SVGPathSegCurvetoQuadraticSmoothAbs)
-> JSVal
-> JSM SVGPathSegCurvetoQuadraticSmoothAbs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegCurvetoQuadraticSmoothAbs
SVGPathSegCurvetoQuadraticSmoothAbs
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegCurvetoQuadraticSmoothAbs where
  makeObject :: SVGPathSegCurvetoQuadraticSmoothAbs -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegCurvetoQuadraticSmoothAbs -> JSVal)
-> SVGPathSegCurvetoQuadraticSmoothAbs
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoQuadraticSmoothAbs -> JSVal
unSVGPathSegCurvetoQuadraticSmoothAbs

instance IsSVGPathSeg SVGPathSegCurvetoQuadraticSmoothAbs
instance IsGObject SVGPathSegCurvetoQuadraticSmoothAbs where
  typeGType :: SVGPathSegCurvetoQuadraticSmoothAbs -> JSM GType
typeGType SVGPathSegCurvetoQuadraticSmoothAbs
_ = JSM GType
gTypeSVGPathSegCurvetoQuadraticSmoothAbs
  {-# INLINE typeGType #-}

noSVGPathSegCurvetoQuadraticSmoothAbs :: Maybe SVGPathSegCurvetoQuadraticSmoothAbs
noSVGPathSegCurvetoQuadraticSmoothAbs :: Maybe SVGPathSegCurvetoQuadraticSmoothAbs
noSVGPathSegCurvetoQuadraticSmoothAbs = Maybe SVGPathSegCurvetoQuadraticSmoothAbs
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegCurvetoQuadraticSmoothAbs #-}

gTypeSVGPathSegCurvetoQuadraticSmoothAbs :: JSM GType
gTypeSVGPathSegCurvetoQuadraticSmoothAbs :: JSM GType
gTypeSVGPathSegCurvetoQuadraticSmoothAbs = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegCurvetoQuadraticSmoothAbs"

-- | Functions for this inteface are in "JSDOM.SVGPathSegCurvetoQuadraticSmoothRel".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegCurvetoQuadraticSmoothRel Mozilla SVGPathSegCurvetoQuadraticSmoothRel documentation>
newtype SVGPathSegCurvetoQuadraticSmoothRel = SVGPathSegCurvetoQuadraticSmoothRel { SVGPathSegCurvetoQuadraticSmoothRel -> JSVal
unSVGPathSegCurvetoQuadraticSmoothRel :: JSVal }

instance PToJSVal SVGPathSegCurvetoQuadraticSmoothRel where
  pToJSVal :: SVGPathSegCurvetoQuadraticSmoothRel -> JSVal
pToJSVal = SVGPathSegCurvetoQuadraticSmoothRel -> JSVal
unSVGPathSegCurvetoQuadraticSmoothRel
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegCurvetoQuadraticSmoothRel where
  pFromJSVal :: JSVal -> SVGPathSegCurvetoQuadraticSmoothRel
pFromJSVal = JSVal -> SVGPathSegCurvetoQuadraticSmoothRel
SVGPathSegCurvetoQuadraticSmoothRel
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegCurvetoQuadraticSmoothRel where
  toJSVal :: SVGPathSegCurvetoQuadraticSmoothRel -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegCurvetoQuadraticSmoothRel -> JSVal)
-> SVGPathSegCurvetoQuadraticSmoothRel
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoQuadraticSmoothRel -> JSVal
unSVGPathSegCurvetoQuadraticSmoothRel
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegCurvetoQuadraticSmoothRel where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegCurvetoQuadraticSmoothRel)
fromJSVal JSVal
v = (JSVal -> SVGPathSegCurvetoQuadraticSmoothRel)
-> Maybe JSVal -> Maybe SVGPathSegCurvetoQuadraticSmoothRel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegCurvetoQuadraticSmoothRel
SVGPathSegCurvetoQuadraticSmoothRel (Maybe JSVal -> Maybe SVGPathSegCurvetoQuadraticSmoothRel)
-> JSM (Maybe JSVal)
-> JSM (Maybe SVGPathSegCurvetoQuadraticSmoothRel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegCurvetoQuadraticSmoothRel
fromJSValUnchecked = SVGPathSegCurvetoQuadraticSmoothRel
-> JSM SVGPathSegCurvetoQuadraticSmoothRel
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegCurvetoQuadraticSmoothRel
 -> JSM SVGPathSegCurvetoQuadraticSmoothRel)
-> (JSVal -> SVGPathSegCurvetoQuadraticSmoothRel)
-> JSVal
-> JSM SVGPathSegCurvetoQuadraticSmoothRel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegCurvetoQuadraticSmoothRel
SVGPathSegCurvetoQuadraticSmoothRel
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegCurvetoQuadraticSmoothRel where
  makeObject :: SVGPathSegCurvetoQuadraticSmoothRel -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegCurvetoQuadraticSmoothRel -> JSVal)
-> SVGPathSegCurvetoQuadraticSmoothRel
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegCurvetoQuadraticSmoothRel -> JSVal
unSVGPathSegCurvetoQuadraticSmoothRel

instance IsSVGPathSeg SVGPathSegCurvetoQuadraticSmoothRel
instance IsGObject SVGPathSegCurvetoQuadraticSmoothRel where
  typeGType :: SVGPathSegCurvetoQuadraticSmoothRel -> JSM GType
typeGType SVGPathSegCurvetoQuadraticSmoothRel
_ = JSM GType
gTypeSVGPathSegCurvetoQuadraticSmoothRel
  {-# INLINE typeGType #-}

noSVGPathSegCurvetoQuadraticSmoothRel :: Maybe SVGPathSegCurvetoQuadraticSmoothRel
noSVGPathSegCurvetoQuadraticSmoothRel :: Maybe SVGPathSegCurvetoQuadraticSmoothRel
noSVGPathSegCurvetoQuadraticSmoothRel = Maybe SVGPathSegCurvetoQuadraticSmoothRel
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegCurvetoQuadraticSmoothRel #-}

gTypeSVGPathSegCurvetoQuadraticSmoothRel :: JSM GType
gTypeSVGPathSegCurvetoQuadraticSmoothRel :: JSM GType
gTypeSVGPathSegCurvetoQuadraticSmoothRel = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegCurvetoQuadraticSmoothRel"

-- | Functions for this inteface are in "JSDOM.SVGPathSegLinetoAbs".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegLinetoAbs Mozilla SVGPathSegLinetoAbs documentation>
newtype SVGPathSegLinetoAbs = SVGPathSegLinetoAbs { SVGPathSegLinetoAbs -> JSVal
unSVGPathSegLinetoAbs :: JSVal }

instance PToJSVal SVGPathSegLinetoAbs where
  pToJSVal :: SVGPathSegLinetoAbs -> JSVal
pToJSVal = SVGPathSegLinetoAbs -> JSVal
unSVGPathSegLinetoAbs
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegLinetoAbs where
  pFromJSVal :: JSVal -> SVGPathSegLinetoAbs
pFromJSVal = JSVal -> SVGPathSegLinetoAbs
SVGPathSegLinetoAbs
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegLinetoAbs where
  toJSVal :: SVGPathSegLinetoAbs -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegLinetoAbs -> JSVal)
-> SVGPathSegLinetoAbs
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoAbs -> JSVal
unSVGPathSegLinetoAbs
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegLinetoAbs where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegLinetoAbs)
fromJSVal JSVal
v = (JSVal -> SVGPathSegLinetoAbs)
-> Maybe JSVal -> Maybe SVGPathSegLinetoAbs
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegLinetoAbs
SVGPathSegLinetoAbs (Maybe JSVal -> Maybe SVGPathSegLinetoAbs)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegLinetoAbs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegLinetoAbs
fromJSValUnchecked = SVGPathSegLinetoAbs -> JSM SVGPathSegLinetoAbs
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegLinetoAbs -> JSM SVGPathSegLinetoAbs)
-> (JSVal -> SVGPathSegLinetoAbs)
-> JSVal
-> JSM SVGPathSegLinetoAbs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegLinetoAbs
SVGPathSegLinetoAbs
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegLinetoAbs where
  makeObject :: SVGPathSegLinetoAbs -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegLinetoAbs -> JSVal)
-> SVGPathSegLinetoAbs
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoAbs -> JSVal
unSVGPathSegLinetoAbs

instance IsSVGPathSeg SVGPathSegLinetoAbs
instance IsGObject SVGPathSegLinetoAbs where
  typeGType :: SVGPathSegLinetoAbs -> JSM GType
typeGType SVGPathSegLinetoAbs
_ = JSM GType
gTypeSVGPathSegLinetoAbs
  {-# INLINE typeGType #-}

noSVGPathSegLinetoAbs :: Maybe SVGPathSegLinetoAbs
noSVGPathSegLinetoAbs :: Maybe SVGPathSegLinetoAbs
noSVGPathSegLinetoAbs = Maybe SVGPathSegLinetoAbs
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegLinetoAbs #-}

gTypeSVGPathSegLinetoAbs :: JSM GType
gTypeSVGPathSegLinetoAbs :: JSM GType
gTypeSVGPathSegLinetoAbs = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegLinetoAbs"

-- | Functions for this inteface are in "JSDOM.SVGPathSegLinetoHorizontalAbs".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegLinetoHorizontalAbs Mozilla SVGPathSegLinetoHorizontalAbs documentation>
newtype SVGPathSegLinetoHorizontalAbs = SVGPathSegLinetoHorizontalAbs { SVGPathSegLinetoHorizontalAbs -> JSVal
unSVGPathSegLinetoHorizontalAbs :: JSVal }

instance PToJSVal SVGPathSegLinetoHorizontalAbs where
  pToJSVal :: SVGPathSegLinetoHorizontalAbs -> JSVal
pToJSVal = SVGPathSegLinetoHorizontalAbs -> JSVal
unSVGPathSegLinetoHorizontalAbs
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegLinetoHorizontalAbs where
  pFromJSVal :: JSVal -> SVGPathSegLinetoHorizontalAbs
pFromJSVal = JSVal -> SVGPathSegLinetoHorizontalAbs
SVGPathSegLinetoHorizontalAbs
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegLinetoHorizontalAbs where
  toJSVal :: SVGPathSegLinetoHorizontalAbs -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegLinetoHorizontalAbs -> JSVal)
-> SVGPathSegLinetoHorizontalAbs
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoHorizontalAbs -> JSVal
unSVGPathSegLinetoHorizontalAbs
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegLinetoHorizontalAbs where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegLinetoHorizontalAbs)
fromJSVal JSVal
v = (JSVal -> SVGPathSegLinetoHorizontalAbs)
-> Maybe JSVal -> Maybe SVGPathSegLinetoHorizontalAbs
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegLinetoHorizontalAbs
SVGPathSegLinetoHorizontalAbs (Maybe JSVal -> Maybe SVGPathSegLinetoHorizontalAbs)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegLinetoHorizontalAbs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegLinetoHorizontalAbs
fromJSValUnchecked = SVGPathSegLinetoHorizontalAbs -> JSM SVGPathSegLinetoHorizontalAbs
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegLinetoHorizontalAbs
 -> JSM SVGPathSegLinetoHorizontalAbs)
-> (JSVal -> SVGPathSegLinetoHorizontalAbs)
-> JSVal
-> JSM SVGPathSegLinetoHorizontalAbs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegLinetoHorizontalAbs
SVGPathSegLinetoHorizontalAbs
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegLinetoHorizontalAbs where
  makeObject :: SVGPathSegLinetoHorizontalAbs -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegLinetoHorizontalAbs -> JSVal)
-> SVGPathSegLinetoHorizontalAbs
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoHorizontalAbs -> JSVal
unSVGPathSegLinetoHorizontalAbs

instance IsSVGPathSeg SVGPathSegLinetoHorizontalAbs
instance IsGObject SVGPathSegLinetoHorizontalAbs where
  typeGType :: SVGPathSegLinetoHorizontalAbs -> JSM GType
typeGType SVGPathSegLinetoHorizontalAbs
_ = JSM GType
gTypeSVGPathSegLinetoHorizontalAbs
  {-# INLINE typeGType #-}

noSVGPathSegLinetoHorizontalAbs :: Maybe SVGPathSegLinetoHorizontalAbs
noSVGPathSegLinetoHorizontalAbs :: Maybe SVGPathSegLinetoHorizontalAbs
noSVGPathSegLinetoHorizontalAbs = Maybe SVGPathSegLinetoHorizontalAbs
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegLinetoHorizontalAbs #-}

gTypeSVGPathSegLinetoHorizontalAbs :: JSM GType
gTypeSVGPathSegLinetoHorizontalAbs :: JSM GType
gTypeSVGPathSegLinetoHorizontalAbs = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegLinetoHorizontalAbs"

-- | Functions for this inteface are in "JSDOM.SVGPathSegLinetoHorizontalRel".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegLinetoHorizontalRel Mozilla SVGPathSegLinetoHorizontalRel documentation>
newtype SVGPathSegLinetoHorizontalRel = SVGPathSegLinetoHorizontalRel { SVGPathSegLinetoHorizontalRel -> JSVal
unSVGPathSegLinetoHorizontalRel :: JSVal }

instance PToJSVal SVGPathSegLinetoHorizontalRel where
  pToJSVal :: SVGPathSegLinetoHorizontalRel -> JSVal
pToJSVal = SVGPathSegLinetoHorizontalRel -> JSVal
unSVGPathSegLinetoHorizontalRel
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegLinetoHorizontalRel where
  pFromJSVal :: JSVal -> SVGPathSegLinetoHorizontalRel
pFromJSVal = JSVal -> SVGPathSegLinetoHorizontalRel
SVGPathSegLinetoHorizontalRel
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegLinetoHorizontalRel where
  toJSVal :: SVGPathSegLinetoHorizontalRel -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegLinetoHorizontalRel -> JSVal)
-> SVGPathSegLinetoHorizontalRel
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoHorizontalRel -> JSVal
unSVGPathSegLinetoHorizontalRel
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegLinetoHorizontalRel where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegLinetoHorizontalRel)
fromJSVal JSVal
v = (JSVal -> SVGPathSegLinetoHorizontalRel)
-> Maybe JSVal -> Maybe SVGPathSegLinetoHorizontalRel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegLinetoHorizontalRel
SVGPathSegLinetoHorizontalRel (Maybe JSVal -> Maybe SVGPathSegLinetoHorizontalRel)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegLinetoHorizontalRel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegLinetoHorizontalRel
fromJSValUnchecked = SVGPathSegLinetoHorizontalRel -> JSM SVGPathSegLinetoHorizontalRel
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegLinetoHorizontalRel
 -> JSM SVGPathSegLinetoHorizontalRel)
-> (JSVal -> SVGPathSegLinetoHorizontalRel)
-> JSVal
-> JSM SVGPathSegLinetoHorizontalRel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegLinetoHorizontalRel
SVGPathSegLinetoHorizontalRel
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegLinetoHorizontalRel where
  makeObject :: SVGPathSegLinetoHorizontalRel -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegLinetoHorizontalRel -> JSVal)
-> SVGPathSegLinetoHorizontalRel
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoHorizontalRel -> JSVal
unSVGPathSegLinetoHorizontalRel

instance IsSVGPathSeg SVGPathSegLinetoHorizontalRel
instance IsGObject SVGPathSegLinetoHorizontalRel where
  typeGType :: SVGPathSegLinetoHorizontalRel -> JSM GType
typeGType SVGPathSegLinetoHorizontalRel
_ = JSM GType
gTypeSVGPathSegLinetoHorizontalRel
  {-# INLINE typeGType #-}

noSVGPathSegLinetoHorizontalRel :: Maybe SVGPathSegLinetoHorizontalRel
noSVGPathSegLinetoHorizontalRel :: Maybe SVGPathSegLinetoHorizontalRel
noSVGPathSegLinetoHorizontalRel = Maybe SVGPathSegLinetoHorizontalRel
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegLinetoHorizontalRel #-}

gTypeSVGPathSegLinetoHorizontalRel :: JSM GType
gTypeSVGPathSegLinetoHorizontalRel :: JSM GType
gTypeSVGPathSegLinetoHorizontalRel = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegLinetoHorizontalRel"

-- | Functions for this inteface are in "JSDOM.SVGPathSegLinetoRel".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegLinetoRel Mozilla SVGPathSegLinetoRel documentation>
newtype SVGPathSegLinetoRel = SVGPathSegLinetoRel { SVGPathSegLinetoRel -> JSVal
unSVGPathSegLinetoRel :: JSVal }

instance PToJSVal SVGPathSegLinetoRel where
  pToJSVal :: SVGPathSegLinetoRel -> JSVal
pToJSVal = SVGPathSegLinetoRel -> JSVal
unSVGPathSegLinetoRel
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegLinetoRel where
  pFromJSVal :: JSVal -> SVGPathSegLinetoRel
pFromJSVal = JSVal -> SVGPathSegLinetoRel
SVGPathSegLinetoRel
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegLinetoRel where
  toJSVal :: SVGPathSegLinetoRel -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegLinetoRel -> JSVal)
-> SVGPathSegLinetoRel
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoRel -> JSVal
unSVGPathSegLinetoRel
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegLinetoRel where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegLinetoRel)
fromJSVal JSVal
v = (JSVal -> SVGPathSegLinetoRel)
-> Maybe JSVal -> Maybe SVGPathSegLinetoRel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegLinetoRel
SVGPathSegLinetoRel (Maybe JSVal -> Maybe SVGPathSegLinetoRel)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegLinetoRel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegLinetoRel
fromJSValUnchecked = SVGPathSegLinetoRel -> JSM SVGPathSegLinetoRel
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegLinetoRel -> JSM SVGPathSegLinetoRel)
-> (JSVal -> SVGPathSegLinetoRel)
-> JSVal
-> JSM SVGPathSegLinetoRel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegLinetoRel
SVGPathSegLinetoRel
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegLinetoRel where
  makeObject :: SVGPathSegLinetoRel -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegLinetoRel -> JSVal)
-> SVGPathSegLinetoRel
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoRel -> JSVal
unSVGPathSegLinetoRel

instance IsSVGPathSeg SVGPathSegLinetoRel
instance IsGObject SVGPathSegLinetoRel where
  typeGType :: SVGPathSegLinetoRel -> JSM GType
typeGType SVGPathSegLinetoRel
_ = JSM GType
gTypeSVGPathSegLinetoRel
  {-# INLINE typeGType #-}

noSVGPathSegLinetoRel :: Maybe SVGPathSegLinetoRel
noSVGPathSegLinetoRel :: Maybe SVGPathSegLinetoRel
noSVGPathSegLinetoRel = Maybe SVGPathSegLinetoRel
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegLinetoRel #-}

gTypeSVGPathSegLinetoRel :: JSM GType
gTypeSVGPathSegLinetoRel :: JSM GType
gTypeSVGPathSegLinetoRel = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegLinetoRel"

-- | Functions for this inteface are in "JSDOM.SVGPathSegLinetoVerticalAbs".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegLinetoVerticalAbs Mozilla SVGPathSegLinetoVerticalAbs documentation>
newtype SVGPathSegLinetoVerticalAbs = SVGPathSegLinetoVerticalAbs { SVGPathSegLinetoVerticalAbs -> JSVal
unSVGPathSegLinetoVerticalAbs :: JSVal }

instance PToJSVal SVGPathSegLinetoVerticalAbs where
  pToJSVal :: SVGPathSegLinetoVerticalAbs -> JSVal
pToJSVal = SVGPathSegLinetoVerticalAbs -> JSVal
unSVGPathSegLinetoVerticalAbs
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegLinetoVerticalAbs where
  pFromJSVal :: JSVal -> SVGPathSegLinetoVerticalAbs
pFromJSVal = JSVal -> SVGPathSegLinetoVerticalAbs
SVGPathSegLinetoVerticalAbs
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegLinetoVerticalAbs where
  toJSVal :: SVGPathSegLinetoVerticalAbs -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegLinetoVerticalAbs -> JSVal)
-> SVGPathSegLinetoVerticalAbs
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoVerticalAbs -> JSVal
unSVGPathSegLinetoVerticalAbs
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegLinetoVerticalAbs where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegLinetoVerticalAbs)
fromJSVal JSVal
v = (JSVal -> SVGPathSegLinetoVerticalAbs)
-> Maybe JSVal -> Maybe SVGPathSegLinetoVerticalAbs
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegLinetoVerticalAbs
SVGPathSegLinetoVerticalAbs (Maybe JSVal -> Maybe SVGPathSegLinetoVerticalAbs)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegLinetoVerticalAbs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegLinetoVerticalAbs
fromJSValUnchecked = SVGPathSegLinetoVerticalAbs -> JSM SVGPathSegLinetoVerticalAbs
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegLinetoVerticalAbs -> JSM SVGPathSegLinetoVerticalAbs)
-> (JSVal -> SVGPathSegLinetoVerticalAbs)
-> JSVal
-> JSM SVGPathSegLinetoVerticalAbs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegLinetoVerticalAbs
SVGPathSegLinetoVerticalAbs
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegLinetoVerticalAbs where
  makeObject :: SVGPathSegLinetoVerticalAbs -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegLinetoVerticalAbs -> JSVal)
-> SVGPathSegLinetoVerticalAbs
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoVerticalAbs -> JSVal
unSVGPathSegLinetoVerticalAbs

instance IsSVGPathSeg SVGPathSegLinetoVerticalAbs
instance IsGObject SVGPathSegLinetoVerticalAbs where
  typeGType :: SVGPathSegLinetoVerticalAbs -> JSM GType
typeGType SVGPathSegLinetoVerticalAbs
_ = JSM GType
gTypeSVGPathSegLinetoVerticalAbs
  {-# INLINE typeGType #-}

noSVGPathSegLinetoVerticalAbs :: Maybe SVGPathSegLinetoVerticalAbs
noSVGPathSegLinetoVerticalAbs :: Maybe SVGPathSegLinetoVerticalAbs
noSVGPathSegLinetoVerticalAbs = Maybe SVGPathSegLinetoVerticalAbs
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegLinetoVerticalAbs #-}

gTypeSVGPathSegLinetoVerticalAbs :: JSM GType
gTypeSVGPathSegLinetoVerticalAbs :: JSM GType
gTypeSVGPathSegLinetoVerticalAbs = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegLinetoVerticalAbs"

-- | Functions for this inteface are in "JSDOM.SVGPathSegLinetoVerticalRel".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegLinetoVerticalRel Mozilla SVGPathSegLinetoVerticalRel documentation>
newtype SVGPathSegLinetoVerticalRel = SVGPathSegLinetoVerticalRel { SVGPathSegLinetoVerticalRel -> JSVal
unSVGPathSegLinetoVerticalRel :: JSVal }

instance PToJSVal SVGPathSegLinetoVerticalRel where
  pToJSVal :: SVGPathSegLinetoVerticalRel -> JSVal
pToJSVal = SVGPathSegLinetoVerticalRel -> JSVal
unSVGPathSegLinetoVerticalRel
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegLinetoVerticalRel where
  pFromJSVal :: JSVal -> SVGPathSegLinetoVerticalRel
pFromJSVal = JSVal -> SVGPathSegLinetoVerticalRel
SVGPathSegLinetoVerticalRel
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegLinetoVerticalRel where
  toJSVal :: SVGPathSegLinetoVerticalRel -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegLinetoVerticalRel -> JSVal)
-> SVGPathSegLinetoVerticalRel
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoVerticalRel -> JSVal
unSVGPathSegLinetoVerticalRel
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegLinetoVerticalRel where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegLinetoVerticalRel)
fromJSVal JSVal
v = (JSVal -> SVGPathSegLinetoVerticalRel)
-> Maybe JSVal -> Maybe SVGPathSegLinetoVerticalRel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegLinetoVerticalRel
SVGPathSegLinetoVerticalRel (Maybe JSVal -> Maybe SVGPathSegLinetoVerticalRel)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegLinetoVerticalRel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegLinetoVerticalRel
fromJSValUnchecked = SVGPathSegLinetoVerticalRel -> JSM SVGPathSegLinetoVerticalRel
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegLinetoVerticalRel -> JSM SVGPathSegLinetoVerticalRel)
-> (JSVal -> SVGPathSegLinetoVerticalRel)
-> JSVal
-> JSM SVGPathSegLinetoVerticalRel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegLinetoVerticalRel
SVGPathSegLinetoVerticalRel
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegLinetoVerticalRel where
  makeObject :: SVGPathSegLinetoVerticalRel -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegLinetoVerticalRel -> JSVal)
-> SVGPathSegLinetoVerticalRel
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegLinetoVerticalRel -> JSVal
unSVGPathSegLinetoVerticalRel

instance IsSVGPathSeg SVGPathSegLinetoVerticalRel
instance IsGObject SVGPathSegLinetoVerticalRel where
  typeGType :: SVGPathSegLinetoVerticalRel -> JSM GType
typeGType SVGPathSegLinetoVerticalRel
_ = JSM GType
gTypeSVGPathSegLinetoVerticalRel
  {-# INLINE typeGType #-}

noSVGPathSegLinetoVerticalRel :: Maybe SVGPathSegLinetoVerticalRel
noSVGPathSegLinetoVerticalRel :: Maybe SVGPathSegLinetoVerticalRel
noSVGPathSegLinetoVerticalRel = Maybe SVGPathSegLinetoVerticalRel
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegLinetoVerticalRel #-}

gTypeSVGPathSegLinetoVerticalRel :: JSM GType
gTypeSVGPathSegLinetoVerticalRel :: JSM GType
gTypeSVGPathSegLinetoVerticalRel = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegLinetoVerticalRel"

-- | Functions for this inteface are in "JSDOM.SVGPathSegList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegList Mozilla SVGPathSegList documentation>
newtype SVGPathSegList = SVGPathSegList { SVGPathSegList -> JSVal
unSVGPathSegList :: JSVal }

instance PToJSVal SVGPathSegList where
  pToJSVal :: SVGPathSegList -> JSVal
pToJSVal = SVGPathSegList -> JSVal
unSVGPathSegList
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegList where
  pFromJSVal :: JSVal -> SVGPathSegList
pFromJSVal = JSVal -> SVGPathSegList
SVGPathSegList
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegList where
  toJSVal :: SVGPathSegList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegList -> JSVal) -> SVGPathSegList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegList -> JSVal
unSVGPathSegList
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegList where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegList)
fromJSVal JSVal
v = (JSVal -> SVGPathSegList) -> Maybe JSVal -> Maybe SVGPathSegList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegList
SVGPathSegList (Maybe JSVal -> Maybe SVGPathSegList)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegList
fromJSValUnchecked = SVGPathSegList -> JSM SVGPathSegList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegList -> JSM SVGPathSegList)
-> (JSVal -> SVGPathSegList) -> JSVal -> JSM SVGPathSegList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegList
SVGPathSegList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegList where
  makeObject :: SVGPathSegList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegList -> JSVal) -> SVGPathSegList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegList -> JSVal
unSVGPathSegList

instance IsGObject SVGPathSegList where
  typeGType :: SVGPathSegList -> JSM GType
typeGType SVGPathSegList
_ = JSM GType
gTypeSVGPathSegList
  {-# INLINE typeGType #-}

noSVGPathSegList :: Maybe SVGPathSegList
noSVGPathSegList :: Maybe SVGPathSegList
noSVGPathSegList = Maybe SVGPathSegList
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegList #-}

gTypeSVGPathSegList :: JSM GType
gTypeSVGPathSegList :: JSM GType
gTypeSVGPathSegList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegList"

-- | Functions for this inteface are in "JSDOM.SVGPathSegMovetoAbs".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegMovetoAbs Mozilla SVGPathSegMovetoAbs documentation>
newtype SVGPathSegMovetoAbs = SVGPathSegMovetoAbs { SVGPathSegMovetoAbs -> JSVal
unSVGPathSegMovetoAbs :: JSVal }

instance PToJSVal SVGPathSegMovetoAbs where
  pToJSVal :: SVGPathSegMovetoAbs -> JSVal
pToJSVal = SVGPathSegMovetoAbs -> JSVal
unSVGPathSegMovetoAbs
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegMovetoAbs where
  pFromJSVal :: JSVal -> SVGPathSegMovetoAbs
pFromJSVal = JSVal -> SVGPathSegMovetoAbs
SVGPathSegMovetoAbs
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegMovetoAbs where
  toJSVal :: SVGPathSegMovetoAbs -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegMovetoAbs -> JSVal)
-> SVGPathSegMovetoAbs
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegMovetoAbs -> JSVal
unSVGPathSegMovetoAbs
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegMovetoAbs where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegMovetoAbs)
fromJSVal JSVal
v = (JSVal -> SVGPathSegMovetoAbs)
-> Maybe JSVal -> Maybe SVGPathSegMovetoAbs
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegMovetoAbs
SVGPathSegMovetoAbs (Maybe JSVal -> Maybe SVGPathSegMovetoAbs)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegMovetoAbs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegMovetoAbs
fromJSValUnchecked = SVGPathSegMovetoAbs -> JSM SVGPathSegMovetoAbs
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegMovetoAbs -> JSM SVGPathSegMovetoAbs)
-> (JSVal -> SVGPathSegMovetoAbs)
-> JSVal
-> JSM SVGPathSegMovetoAbs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegMovetoAbs
SVGPathSegMovetoAbs
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegMovetoAbs where
  makeObject :: SVGPathSegMovetoAbs -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegMovetoAbs -> JSVal)
-> SVGPathSegMovetoAbs
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegMovetoAbs -> JSVal
unSVGPathSegMovetoAbs

instance IsSVGPathSeg SVGPathSegMovetoAbs
instance IsGObject SVGPathSegMovetoAbs where
  typeGType :: SVGPathSegMovetoAbs -> JSM GType
typeGType SVGPathSegMovetoAbs
_ = JSM GType
gTypeSVGPathSegMovetoAbs
  {-# INLINE typeGType #-}

noSVGPathSegMovetoAbs :: Maybe SVGPathSegMovetoAbs
noSVGPathSegMovetoAbs :: Maybe SVGPathSegMovetoAbs
noSVGPathSegMovetoAbs = Maybe SVGPathSegMovetoAbs
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegMovetoAbs #-}

gTypeSVGPathSegMovetoAbs :: JSM GType
gTypeSVGPathSegMovetoAbs :: JSM GType
gTypeSVGPathSegMovetoAbs = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegMovetoAbs"

-- | Functions for this inteface are in "JSDOM.SVGPathSegMovetoRel".
-- Base interface functions are in:
--
--     * "JSDOM.SVGPathSeg"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegMovetoRel Mozilla SVGPathSegMovetoRel documentation>
newtype SVGPathSegMovetoRel = SVGPathSegMovetoRel { SVGPathSegMovetoRel -> JSVal
unSVGPathSegMovetoRel :: JSVal }

instance PToJSVal SVGPathSegMovetoRel where
  pToJSVal :: SVGPathSegMovetoRel -> JSVal
pToJSVal = SVGPathSegMovetoRel -> JSVal
unSVGPathSegMovetoRel
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPathSegMovetoRel where
  pFromJSVal :: JSVal -> SVGPathSegMovetoRel
pFromJSVal = JSVal -> SVGPathSegMovetoRel
SVGPathSegMovetoRel
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPathSegMovetoRel where
  toJSVal :: SVGPathSegMovetoRel -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPathSegMovetoRel -> JSVal)
-> SVGPathSegMovetoRel
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegMovetoRel -> JSVal
unSVGPathSegMovetoRel
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPathSegMovetoRel where
  fromJSVal :: JSVal -> JSM (Maybe SVGPathSegMovetoRel)
fromJSVal JSVal
v = (JSVal -> SVGPathSegMovetoRel)
-> Maybe JSVal -> Maybe SVGPathSegMovetoRel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPathSegMovetoRel
SVGPathSegMovetoRel (Maybe JSVal -> Maybe SVGPathSegMovetoRel)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPathSegMovetoRel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPathSegMovetoRel
fromJSValUnchecked = SVGPathSegMovetoRel -> JSM SVGPathSegMovetoRel
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPathSegMovetoRel -> JSM SVGPathSegMovetoRel)
-> (JSVal -> SVGPathSegMovetoRel)
-> JSVal
-> JSM SVGPathSegMovetoRel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPathSegMovetoRel
SVGPathSegMovetoRel
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPathSegMovetoRel where
  makeObject :: SVGPathSegMovetoRel -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPathSegMovetoRel -> JSVal)
-> SVGPathSegMovetoRel
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPathSegMovetoRel -> JSVal
unSVGPathSegMovetoRel

instance IsSVGPathSeg SVGPathSegMovetoRel
instance IsGObject SVGPathSegMovetoRel where
  typeGType :: SVGPathSegMovetoRel -> JSM GType
typeGType SVGPathSegMovetoRel
_ = JSM GType
gTypeSVGPathSegMovetoRel
  {-# INLINE typeGType #-}

noSVGPathSegMovetoRel :: Maybe SVGPathSegMovetoRel
noSVGPathSegMovetoRel :: Maybe SVGPathSegMovetoRel
noSVGPathSegMovetoRel = Maybe SVGPathSegMovetoRel
forall a. Maybe a
Nothing
{-# INLINE noSVGPathSegMovetoRel #-}

gTypeSVGPathSegMovetoRel :: JSM GType
gTypeSVGPathSegMovetoRel :: JSM GType
gTypeSVGPathSegMovetoRel = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPathSegMovetoRel"

-- | Functions for this inteface are in "JSDOM.SVGPatternElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGFitToViewBox"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPatternElement Mozilla SVGPatternElement documentation>
newtype SVGPatternElement = SVGPatternElement { SVGPatternElement -> JSVal
unSVGPatternElement :: JSVal }

instance PToJSVal SVGPatternElement where
  pToJSVal :: SVGPatternElement -> JSVal
pToJSVal = SVGPatternElement -> JSVal
unSVGPatternElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPatternElement where
  pFromJSVal :: JSVal -> SVGPatternElement
pFromJSVal = JSVal -> SVGPatternElement
SVGPatternElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPatternElement where
  toJSVal :: SVGPatternElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPatternElement -> JSVal) -> SVGPatternElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPatternElement -> JSVal
unSVGPatternElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPatternElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGPatternElement)
fromJSVal JSVal
v = (JSVal -> SVGPatternElement)
-> Maybe JSVal -> Maybe SVGPatternElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPatternElement
SVGPatternElement (Maybe JSVal -> Maybe SVGPatternElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPatternElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPatternElement
fromJSValUnchecked = SVGPatternElement -> JSM SVGPatternElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPatternElement -> JSM SVGPatternElement)
-> (JSVal -> SVGPatternElement) -> JSVal -> JSM SVGPatternElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPatternElement
SVGPatternElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPatternElement where
  makeObject :: SVGPatternElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPatternElement -> JSVal) -> SVGPatternElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPatternElement -> JSVal
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 :: SVGPatternElement -> JSM GType
typeGType SVGPatternElement
_ = JSM GType
gTypeSVGPatternElement
  {-# INLINE typeGType #-}

noSVGPatternElement :: Maybe SVGPatternElement
noSVGPatternElement :: Maybe SVGPatternElement
noSVGPatternElement = Maybe SVGPatternElement
forall a. Maybe a
Nothing
{-# INLINE noSVGPatternElement #-}

gTypeSVGPatternElement :: JSM GType
gTypeSVGPatternElement :: JSM GType
gTypeSVGPatternElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPatternElement"

-- | Functions for this inteface are in "JSDOM.SVGPoint".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPoint Mozilla SVGPoint documentation>
newtype SVGPoint = SVGPoint { SVGPoint -> JSVal
unSVGPoint :: JSVal }

instance PToJSVal SVGPoint where
  pToJSVal :: SVGPoint -> JSVal
pToJSVal = SVGPoint -> JSVal
unSVGPoint
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPoint where
  pFromJSVal :: JSVal -> SVGPoint
pFromJSVal = JSVal -> SVGPoint
SVGPoint
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPoint where
  toJSVal :: SVGPoint -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPoint -> JSVal) -> SVGPoint -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPoint -> JSVal
unSVGPoint
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPoint where
  fromJSVal :: JSVal -> JSM (Maybe SVGPoint)
fromJSVal JSVal
v = (JSVal -> SVGPoint) -> Maybe JSVal -> Maybe SVGPoint
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPoint
SVGPoint (Maybe JSVal -> Maybe SVGPoint)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPoint)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPoint
fromJSValUnchecked = SVGPoint -> JSM SVGPoint
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPoint -> JSM SVGPoint)
-> (JSVal -> SVGPoint) -> JSVal -> JSM SVGPoint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPoint
SVGPoint
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPoint where
  makeObject :: SVGPoint -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPoint -> JSVal) -> SVGPoint -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPoint -> JSVal
unSVGPoint

instance IsGObject SVGPoint where
  typeGType :: SVGPoint -> JSM GType
typeGType SVGPoint
_ = JSM GType
gTypeSVGPoint
  {-# INLINE typeGType #-}

noSVGPoint :: Maybe SVGPoint
noSVGPoint :: Maybe SVGPoint
noSVGPoint = Maybe SVGPoint
forall a. Maybe a
Nothing
{-# INLINE noSVGPoint #-}

gTypeSVGPoint :: JSM GType
gTypeSVGPoint :: JSM GType
gTypeSVGPoint = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPoint"

-- | Functions for this inteface are in "JSDOM.SVGPointList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPointList Mozilla SVGPointList documentation>
newtype SVGPointList = SVGPointList { SVGPointList -> JSVal
unSVGPointList :: JSVal }

instance PToJSVal SVGPointList where
  pToJSVal :: SVGPointList -> JSVal
pToJSVal = SVGPointList -> JSVal
unSVGPointList
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPointList where
  pFromJSVal :: JSVal -> SVGPointList
pFromJSVal = JSVal -> SVGPointList
SVGPointList
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPointList where
  toJSVal :: SVGPointList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPointList -> JSVal) -> SVGPointList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPointList -> JSVal
unSVGPointList
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPointList where
  fromJSVal :: JSVal -> JSM (Maybe SVGPointList)
fromJSVal JSVal
v = (JSVal -> SVGPointList) -> Maybe JSVal -> Maybe SVGPointList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPointList
SVGPointList (Maybe JSVal -> Maybe SVGPointList)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPointList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPointList
fromJSValUnchecked = SVGPointList -> JSM SVGPointList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPointList -> JSM SVGPointList)
-> (JSVal -> SVGPointList) -> JSVal -> JSM SVGPointList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPointList
SVGPointList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPointList where
  makeObject :: SVGPointList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPointList -> JSVal) -> SVGPointList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPointList -> JSVal
unSVGPointList

instance IsGObject SVGPointList where
  typeGType :: SVGPointList -> JSM GType
typeGType SVGPointList
_ = JSM GType
gTypeSVGPointList
  {-# INLINE typeGType #-}

noSVGPointList :: Maybe SVGPointList
noSVGPointList :: Maybe SVGPointList
noSVGPointList = Maybe SVGPointList
forall a. Maybe a
Nothing
{-# INLINE noSVGPointList #-}

gTypeSVGPointList :: JSM GType
gTypeSVGPointList :: JSM GType
gTypeSVGPointList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPointList"

-- | Functions for this inteface are in "JSDOM.SVGPolygonElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPolygonElement Mozilla SVGPolygonElement documentation>
newtype SVGPolygonElement = SVGPolygonElement { SVGPolygonElement -> JSVal
unSVGPolygonElement :: JSVal }

instance PToJSVal SVGPolygonElement where
  pToJSVal :: SVGPolygonElement -> JSVal
pToJSVal = SVGPolygonElement -> JSVal
unSVGPolygonElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPolygonElement where
  pFromJSVal :: JSVal -> SVGPolygonElement
pFromJSVal = JSVal -> SVGPolygonElement
SVGPolygonElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPolygonElement where
  toJSVal :: SVGPolygonElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPolygonElement -> JSVal) -> SVGPolygonElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPolygonElement -> JSVal
unSVGPolygonElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPolygonElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGPolygonElement)
fromJSVal JSVal
v = (JSVal -> SVGPolygonElement)
-> Maybe JSVal -> Maybe SVGPolygonElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPolygonElement
SVGPolygonElement (Maybe JSVal -> Maybe SVGPolygonElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPolygonElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPolygonElement
fromJSValUnchecked = SVGPolygonElement -> JSM SVGPolygonElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPolygonElement -> JSM SVGPolygonElement)
-> (JSVal -> SVGPolygonElement) -> JSVal -> JSM SVGPolygonElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPolygonElement
SVGPolygonElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPolygonElement where
  makeObject :: SVGPolygonElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPolygonElement -> JSVal) -> SVGPolygonElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPolygonElement -> JSVal
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 :: SVGPolygonElement -> JSM GType
typeGType SVGPolygonElement
_ = JSM GType
gTypeSVGPolygonElement
  {-# INLINE typeGType #-}

noSVGPolygonElement :: Maybe SVGPolygonElement
noSVGPolygonElement :: Maybe SVGPolygonElement
noSVGPolygonElement = Maybe SVGPolygonElement
forall a. Maybe a
Nothing
{-# INLINE noSVGPolygonElement #-}

gTypeSVGPolygonElement :: JSM GType
gTypeSVGPolygonElement :: JSM GType
gTypeSVGPolygonElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPolygonElement"

-- | Functions for this inteface are in "JSDOM.SVGPolylineElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPolylineElement Mozilla SVGPolylineElement documentation>
newtype SVGPolylineElement = SVGPolylineElement { SVGPolylineElement -> JSVal
unSVGPolylineElement :: JSVal }

instance PToJSVal SVGPolylineElement where
  pToJSVal :: SVGPolylineElement -> JSVal
pToJSVal = SVGPolylineElement -> JSVal
unSVGPolylineElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPolylineElement where
  pFromJSVal :: JSVal -> SVGPolylineElement
pFromJSVal = JSVal -> SVGPolylineElement
SVGPolylineElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPolylineElement where
  toJSVal :: SVGPolylineElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPolylineElement -> JSVal) -> SVGPolylineElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPolylineElement -> JSVal
unSVGPolylineElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPolylineElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGPolylineElement)
fromJSVal JSVal
v = (JSVal -> SVGPolylineElement)
-> Maybe JSVal -> Maybe SVGPolylineElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPolylineElement
SVGPolylineElement (Maybe JSVal -> Maybe SVGPolylineElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPolylineElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPolylineElement
fromJSValUnchecked = SVGPolylineElement -> JSM SVGPolylineElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPolylineElement -> JSM SVGPolylineElement)
-> (JSVal -> SVGPolylineElement) -> JSVal -> JSM SVGPolylineElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPolylineElement
SVGPolylineElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPolylineElement where
  makeObject :: SVGPolylineElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPolylineElement -> JSVal)
-> SVGPolylineElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPolylineElement -> JSVal
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 :: SVGPolylineElement -> JSM GType
typeGType SVGPolylineElement
_ = JSM GType
gTypeSVGPolylineElement
  {-# INLINE typeGType #-}

noSVGPolylineElement :: Maybe SVGPolylineElement
noSVGPolylineElement :: Maybe SVGPolylineElement
noSVGPolylineElement = Maybe SVGPolylineElement
forall a. Maybe a
Nothing
{-# INLINE noSVGPolylineElement #-}

gTypeSVGPolylineElement :: JSM GType
gTypeSVGPolylineElement :: JSM GType
gTypeSVGPolylineElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPolylineElement"

-- | Functions for this inteface are in "JSDOM.SVGPreserveAspectRatio".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGPreserveAspectRatio Mozilla SVGPreserveAspectRatio documentation>
newtype SVGPreserveAspectRatio = SVGPreserveAspectRatio { SVGPreserveAspectRatio -> JSVal
unSVGPreserveAspectRatio :: JSVal }

instance PToJSVal SVGPreserveAspectRatio where
  pToJSVal :: SVGPreserveAspectRatio -> JSVal
pToJSVal = SVGPreserveAspectRatio -> JSVal
unSVGPreserveAspectRatio
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGPreserveAspectRatio where
  pFromJSVal :: JSVal -> SVGPreserveAspectRatio
pFromJSVal = JSVal -> SVGPreserveAspectRatio
SVGPreserveAspectRatio
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGPreserveAspectRatio where
  toJSVal :: SVGPreserveAspectRatio -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGPreserveAspectRatio -> JSVal)
-> SVGPreserveAspectRatio
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPreserveAspectRatio -> JSVal
unSVGPreserveAspectRatio
  {-# INLINE toJSVal #-}

instance FromJSVal SVGPreserveAspectRatio where
  fromJSVal :: JSVal -> JSM (Maybe SVGPreserveAspectRatio)
fromJSVal JSVal
v = (JSVal -> SVGPreserveAspectRatio)
-> Maybe JSVal -> Maybe SVGPreserveAspectRatio
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGPreserveAspectRatio
SVGPreserveAspectRatio (Maybe JSVal -> Maybe SVGPreserveAspectRatio)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGPreserveAspectRatio)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGPreserveAspectRatio
fromJSValUnchecked = SVGPreserveAspectRatio -> JSM SVGPreserveAspectRatio
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGPreserveAspectRatio -> JSM SVGPreserveAspectRatio)
-> (JSVal -> SVGPreserveAspectRatio)
-> JSVal
-> JSM SVGPreserveAspectRatio
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGPreserveAspectRatio
SVGPreserveAspectRatio
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGPreserveAspectRatio where
  makeObject :: SVGPreserveAspectRatio -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGPreserveAspectRatio -> JSVal)
-> SVGPreserveAspectRatio
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGPreserveAspectRatio -> JSVal
unSVGPreserveAspectRatio

instance IsGObject SVGPreserveAspectRatio where
  typeGType :: SVGPreserveAspectRatio -> JSM GType
typeGType SVGPreserveAspectRatio
_ = JSM GType
gTypeSVGPreserveAspectRatio
  {-# INLINE typeGType #-}

noSVGPreserveAspectRatio :: Maybe SVGPreserveAspectRatio
noSVGPreserveAspectRatio :: Maybe SVGPreserveAspectRatio
noSVGPreserveAspectRatio = Maybe SVGPreserveAspectRatio
forall a. Maybe a
Nothing
{-# INLINE noSVGPreserveAspectRatio #-}

gTypeSVGPreserveAspectRatio :: JSM GType
gTypeSVGPreserveAspectRatio :: JSM GType
gTypeSVGPreserveAspectRatio = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGPreserveAspectRatio"

-- | Functions for this inteface are in "JSDOM.SVGRadialGradientElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGradientElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGRadialGradientElement Mozilla SVGRadialGradientElement documentation>
newtype SVGRadialGradientElement = SVGRadialGradientElement { SVGRadialGradientElement -> JSVal
unSVGRadialGradientElement :: JSVal }

instance PToJSVal SVGRadialGradientElement where
  pToJSVal :: SVGRadialGradientElement -> JSVal
pToJSVal = SVGRadialGradientElement -> JSVal
unSVGRadialGradientElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGRadialGradientElement where
  pFromJSVal :: JSVal -> SVGRadialGradientElement
pFromJSVal = JSVal -> SVGRadialGradientElement
SVGRadialGradientElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGRadialGradientElement where
  toJSVal :: SVGRadialGradientElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGRadialGradientElement -> JSVal)
-> SVGRadialGradientElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGRadialGradientElement -> JSVal
unSVGRadialGradientElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGRadialGradientElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGRadialGradientElement)
fromJSVal JSVal
v = (JSVal -> SVGRadialGradientElement)
-> Maybe JSVal -> Maybe SVGRadialGradientElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGRadialGradientElement
SVGRadialGradientElement (Maybe JSVal -> Maybe SVGRadialGradientElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGRadialGradientElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGRadialGradientElement
fromJSValUnchecked = SVGRadialGradientElement -> JSM SVGRadialGradientElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGRadialGradientElement -> JSM SVGRadialGradientElement)
-> (JSVal -> SVGRadialGradientElement)
-> JSVal
-> JSM SVGRadialGradientElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGRadialGradientElement
SVGRadialGradientElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGRadialGradientElement where
  makeObject :: SVGRadialGradientElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGRadialGradientElement -> JSVal)
-> SVGRadialGradientElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGRadialGradientElement -> JSVal
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 :: SVGRadialGradientElement -> JSM GType
typeGType SVGRadialGradientElement
_ = JSM GType
gTypeSVGRadialGradientElement
  {-# INLINE typeGType #-}

noSVGRadialGradientElement :: Maybe SVGRadialGradientElement
noSVGRadialGradientElement :: Maybe SVGRadialGradientElement
noSVGRadialGradientElement = Maybe SVGRadialGradientElement
forall a. Maybe a
Nothing
{-# INLINE noSVGRadialGradientElement #-}

gTypeSVGRadialGradientElement :: JSM GType
gTypeSVGRadialGradientElement :: JSM GType
gTypeSVGRadialGradientElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGRadialGradientElement"

-- | Functions for this inteface are in "JSDOM.SVGRect".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGRect Mozilla SVGRect documentation>
newtype SVGRect = SVGRect { SVGRect -> JSVal
unSVGRect :: JSVal }

instance PToJSVal SVGRect where
  pToJSVal :: SVGRect -> JSVal
pToJSVal = SVGRect -> JSVal
unSVGRect
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGRect where
  pFromJSVal :: JSVal -> SVGRect
pFromJSVal = JSVal -> SVGRect
SVGRect
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGRect where
  toJSVal :: SVGRect -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (SVGRect -> JSVal) -> SVGRect -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGRect -> JSVal
unSVGRect
  {-# INLINE toJSVal #-}

instance FromJSVal SVGRect where
  fromJSVal :: JSVal -> JSM (Maybe SVGRect)
fromJSVal JSVal
v = (JSVal -> SVGRect) -> Maybe JSVal -> Maybe SVGRect
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGRect
SVGRect (Maybe JSVal -> Maybe SVGRect)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGRect)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGRect
fromJSValUnchecked = SVGRect -> JSM SVGRect
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGRect -> JSM SVGRect)
-> (JSVal -> SVGRect) -> JSVal -> JSM SVGRect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGRect
SVGRect
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGRect where
  makeObject :: SVGRect -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGRect -> JSVal) -> SVGRect -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGRect -> JSVal
unSVGRect

instance IsGObject SVGRect where
  typeGType :: SVGRect -> JSM GType
typeGType SVGRect
_ = JSM GType
gTypeSVGRect
  {-# INLINE typeGType #-}

noSVGRect :: Maybe SVGRect
noSVGRect :: Maybe SVGRect
noSVGRect = Maybe SVGRect
forall a. Maybe a
Nothing
{-# INLINE noSVGRect #-}

gTypeSVGRect :: JSM GType
gTypeSVGRect :: JSM GType
gTypeSVGRect = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGRect"

-- | Functions for this inteface are in "JSDOM.SVGRectElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGRectElement Mozilla SVGRectElement documentation>
newtype SVGRectElement = SVGRectElement { SVGRectElement -> JSVal
unSVGRectElement :: JSVal }

instance PToJSVal SVGRectElement where
  pToJSVal :: SVGRectElement -> JSVal
pToJSVal = SVGRectElement -> JSVal
unSVGRectElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGRectElement where
  pFromJSVal :: JSVal -> SVGRectElement
pFromJSVal = JSVal -> SVGRectElement
SVGRectElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGRectElement where
  toJSVal :: SVGRectElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGRectElement -> JSVal) -> SVGRectElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGRectElement -> JSVal
unSVGRectElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGRectElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGRectElement)
fromJSVal JSVal
v = (JSVal -> SVGRectElement) -> Maybe JSVal -> Maybe SVGRectElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGRectElement
SVGRectElement (Maybe JSVal -> Maybe SVGRectElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGRectElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGRectElement
fromJSValUnchecked = SVGRectElement -> JSM SVGRectElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGRectElement -> JSM SVGRectElement)
-> (JSVal -> SVGRectElement) -> JSVal -> JSM SVGRectElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGRectElement
SVGRectElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGRectElement where
  makeObject :: SVGRectElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGRectElement -> JSVal) -> SVGRectElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGRectElement -> JSVal
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 :: SVGRectElement -> JSM GType
typeGType SVGRectElement
_ = JSM GType
gTypeSVGRectElement
  {-# INLINE typeGType #-}

noSVGRectElement :: Maybe SVGRectElement
noSVGRectElement :: Maybe SVGRectElement
noSVGRectElement = Maybe SVGRectElement
forall a. Maybe a
Nothing
{-# INLINE noSVGRectElement #-}

gTypeSVGRectElement :: JSM GType
gTypeSVGRectElement :: JSM GType
gTypeSVGRectElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGRectElement"

-- | Functions for this inteface are in "JSDOM.SVGRenderingIntent".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGRenderingIntent Mozilla SVGRenderingIntent documentation>
newtype SVGRenderingIntent = SVGRenderingIntent { SVGRenderingIntent -> JSVal
unSVGRenderingIntent :: JSVal }

instance PToJSVal SVGRenderingIntent where
  pToJSVal :: SVGRenderingIntent -> JSVal
pToJSVal = SVGRenderingIntent -> JSVal
unSVGRenderingIntent
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGRenderingIntent where
  pFromJSVal :: JSVal -> SVGRenderingIntent
pFromJSVal = JSVal -> SVGRenderingIntent
SVGRenderingIntent
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGRenderingIntent where
  toJSVal :: SVGRenderingIntent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGRenderingIntent -> JSVal) -> SVGRenderingIntent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGRenderingIntent -> JSVal
unSVGRenderingIntent
  {-# INLINE toJSVal #-}

instance FromJSVal SVGRenderingIntent where
  fromJSVal :: JSVal -> JSM (Maybe SVGRenderingIntent)
fromJSVal JSVal
v = (JSVal -> SVGRenderingIntent)
-> Maybe JSVal -> Maybe SVGRenderingIntent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGRenderingIntent
SVGRenderingIntent (Maybe JSVal -> Maybe SVGRenderingIntent)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGRenderingIntent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGRenderingIntent
fromJSValUnchecked = SVGRenderingIntent -> JSM SVGRenderingIntent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGRenderingIntent -> JSM SVGRenderingIntent)
-> (JSVal -> SVGRenderingIntent) -> JSVal -> JSM SVGRenderingIntent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGRenderingIntent
SVGRenderingIntent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGRenderingIntent where
  makeObject :: SVGRenderingIntent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGRenderingIntent -> JSVal)
-> SVGRenderingIntent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGRenderingIntent -> JSVal
unSVGRenderingIntent

instance IsGObject SVGRenderingIntent where
  typeGType :: SVGRenderingIntent -> JSM GType
typeGType SVGRenderingIntent
_ = JSM GType
gTypeSVGRenderingIntent
  {-# INLINE typeGType #-}

noSVGRenderingIntent :: Maybe SVGRenderingIntent
noSVGRenderingIntent :: Maybe SVGRenderingIntent
noSVGRenderingIntent = Maybe SVGRenderingIntent
forall a. Maybe a
Nothing
{-# INLINE noSVGRenderingIntent #-}

gTypeSVGRenderingIntent :: JSM GType
gTypeSVGRenderingIntent :: JSM GType
gTypeSVGRenderingIntent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGRenderingIntent"

-- | Functions for this inteface are in "JSDOM.SVGSVGElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGZoomAndPan"
--     * "JSDOM.SVGFitToViewBox"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGSVGElement Mozilla SVGSVGElement documentation>
newtype SVGSVGElement = SVGSVGElement { SVGSVGElement -> JSVal
unSVGSVGElement :: JSVal }

instance PToJSVal SVGSVGElement where
  pToJSVal :: SVGSVGElement -> JSVal
pToJSVal = SVGSVGElement -> JSVal
unSVGSVGElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGSVGElement where
  pFromJSVal :: JSVal -> SVGSVGElement
pFromJSVal = JSVal -> SVGSVGElement
SVGSVGElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGSVGElement where
  toJSVal :: SVGSVGElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGSVGElement -> JSVal) -> SVGSVGElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGSVGElement -> JSVal
unSVGSVGElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGSVGElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGSVGElement)
fromJSVal JSVal
v = (JSVal -> SVGSVGElement) -> Maybe JSVal -> Maybe SVGSVGElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGSVGElement
SVGSVGElement (Maybe JSVal -> Maybe SVGSVGElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGSVGElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGSVGElement
fromJSValUnchecked = SVGSVGElement -> JSM SVGSVGElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGSVGElement -> JSM SVGSVGElement)
-> (JSVal -> SVGSVGElement) -> JSVal -> JSM SVGSVGElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGSVGElement
SVGSVGElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGSVGElement where
  makeObject :: SVGSVGElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGSVGElement -> JSVal) -> SVGSVGElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGSVGElement -> JSVal
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 :: SVGSVGElement -> JSM GType
typeGType SVGSVGElement
_ = JSM GType
gTypeSVGSVGElement
  {-# INLINE typeGType #-}

noSVGSVGElement :: Maybe SVGSVGElement
noSVGSVGElement :: Maybe SVGSVGElement
noSVGSVGElement = Maybe SVGSVGElement
forall a. Maybe a
Nothing
{-# INLINE noSVGSVGElement #-}

gTypeSVGSVGElement :: JSM GType
gTypeSVGSVGElement :: JSM GType
gTypeSVGSVGElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGSVGElement"

-- | Functions for this inteface are in "JSDOM.SVGScriptElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGScriptElement Mozilla SVGScriptElement documentation>
newtype SVGScriptElement = SVGScriptElement { SVGScriptElement -> JSVal
unSVGScriptElement :: JSVal }

instance PToJSVal SVGScriptElement where
  pToJSVal :: SVGScriptElement -> JSVal
pToJSVal = SVGScriptElement -> JSVal
unSVGScriptElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGScriptElement where
  pFromJSVal :: JSVal -> SVGScriptElement
pFromJSVal = JSVal -> SVGScriptElement
SVGScriptElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGScriptElement where
  toJSVal :: SVGScriptElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGScriptElement -> JSVal) -> SVGScriptElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGScriptElement -> JSVal
unSVGScriptElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGScriptElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGScriptElement)
fromJSVal JSVal
v = (JSVal -> SVGScriptElement)
-> Maybe JSVal -> Maybe SVGScriptElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGScriptElement
SVGScriptElement (Maybe JSVal -> Maybe SVGScriptElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGScriptElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGScriptElement
fromJSValUnchecked = SVGScriptElement -> JSM SVGScriptElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGScriptElement -> JSM SVGScriptElement)
-> (JSVal -> SVGScriptElement) -> JSVal -> JSM SVGScriptElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGScriptElement
SVGScriptElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGScriptElement where
  makeObject :: SVGScriptElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGScriptElement -> JSVal) -> SVGScriptElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGScriptElement -> JSVal
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 :: SVGScriptElement -> JSM GType
typeGType SVGScriptElement
_ = JSM GType
gTypeSVGScriptElement
  {-# INLINE typeGType #-}

noSVGScriptElement :: Maybe SVGScriptElement
noSVGScriptElement :: Maybe SVGScriptElement
noSVGScriptElement = Maybe SVGScriptElement
forall a. Maybe a
Nothing
{-# INLINE noSVGScriptElement #-}

gTypeSVGScriptElement :: JSM GType
gTypeSVGScriptElement :: JSM GType
gTypeSVGScriptElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGScriptElement"

-- | Functions for this inteface are in "JSDOM.SVGSetElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGAnimationElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGSetElement Mozilla SVGSetElement documentation>
newtype SVGSetElement = SVGSetElement { SVGSetElement -> JSVal
unSVGSetElement :: JSVal }

instance PToJSVal SVGSetElement where
  pToJSVal :: SVGSetElement -> JSVal
pToJSVal = SVGSetElement -> JSVal
unSVGSetElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGSetElement where
  pFromJSVal :: JSVal -> SVGSetElement
pFromJSVal = JSVal -> SVGSetElement
SVGSetElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGSetElement where
  toJSVal :: SVGSetElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGSetElement -> JSVal) -> SVGSetElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGSetElement -> JSVal
unSVGSetElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGSetElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGSetElement)
fromJSVal JSVal
v = (JSVal -> SVGSetElement) -> Maybe JSVal -> Maybe SVGSetElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGSetElement
SVGSetElement (Maybe JSVal -> Maybe SVGSetElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGSetElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGSetElement
fromJSValUnchecked = SVGSetElement -> JSM SVGSetElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGSetElement -> JSM SVGSetElement)
-> (JSVal -> SVGSetElement) -> JSVal -> JSM SVGSetElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGSetElement
SVGSetElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGSetElement where
  makeObject :: SVGSetElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGSetElement -> JSVal) -> SVGSetElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGSetElement -> JSVal
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 :: SVGSetElement -> JSM GType
typeGType SVGSetElement
_ = JSM GType
gTypeSVGSetElement
  {-# INLINE typeGType #-}

noSVGSetElement :: Maybe SVGSetElement
noSVGSetElement :: Maybe SVGSetElement
noSVGSetElement = Maybe SVGSetElement
forall a. Maybe a
Nothing
{-# INLINE noSVGSetElement #-}

gTypeSVGSetElement :: JSM GType
gTypeSVGSetElement :: JSM GType
gTypeSVGSetElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGSetElement"

-- | Functions for this inteface are in "JSDOM.SVGStopElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGStopElement Mozilla SVGStopElement documentation>
newtype SVGStopElement = SVGStopElement { SVGStopElement -> JSVal
unSVGStopElement :: JSVal }

instance PToJSVal SVGStopElement where
  pToJSVal :: SVGStopElement -> JSVal
pToJSVal = SVGStopElement -> JSVal
unSVGStopElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGStopElement where
  pFromJSVal :: JSVal -> SVGStopElement
pFromJSVal = JSVal -> SVGStopElement
SVGStopElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGStopElement where
  toJSVal :: SVGStopElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGStopElement -> JSVal) -> SVGStopElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGStopElement -> JSVal
unSVGStopElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGStopElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGStopElement)
fromJSVal JSVal
v = (JSVal -> SVGStopElement) -> Maybe JSVal -> Maybe SVGStopElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGStopElement
SVGStopElement (Maybe JSVal -> Maybe SVGStopElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGStopElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGStopElement
fromJSValUnchecked = SVGStopElement -> JSM SVGStopElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGStopElement -> JSM SVGStopElement)
-> (JSVal -> SVGStopElement) -> JSVal -> JSM SVGStopElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGStopElement
SVGStopElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGStopElement where
  makeObject :: SVGStopElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGStopElement -> JSVal) -> SVGStopElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGStopElement -> JSVal
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 :: SVGStopElement -> JSM GType
typeGType SVGStopElement
_ = JSM GType
gTypeSVGStopElement
  {-# INLINE typeGType #-}

noSVGStopElement :: Maybe SVGStopElement
noSVGStopElement :: Maybe SVGStopElement
noSVGStopElement = Maybe SVGStopElement
forall a. Maybe a
Nothing
{-# INLINE noSVGStopElement #-}

gTypeSVGStopElement :: JSM GType
gTypeSVGStopElement :: JSM GType
gTypeSVGStopElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGStopElement"

-- | Functions for this inteface are in "JSDOM.SVGStringList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGStringList Mozilla SVGStringList documentation>
newtype SVGStringList = SVGStringList { SVGStringList -> JSVal
unSVGStringList :: JSVal }

instance PToJSVal SVGStringList where
  pToJSVal :: SVGStringList -> JSVal
pToJSVal = SVGStringList -> JSVal
unSVGStringList
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGStringList where
  pFromJSVal :: JSVal -> SVGStringList
pFromJSVal = JSVal -> SVGStringList
SVGStringList
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGStringList where
  toJSVal :: SVGStringList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGStringList -> JSVal) -> SVGStringList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGStringList -> JSVal
unSVGStringList
  {-# INLINE toJSVal #-}

instance FromJSVal SVGStringList where
  fromJSVal :: JSVal -> JSM (Maybe SVGStringList)
fromJSVal JSVal
v = (JSVal -> SVGStringList) -> Maybe JSVal -> Maybe SVGStringList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGStringList
SVGStringList (Maybe JSVal -> Maybe SVGStringList)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGStringList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGStringList
fromJSValUnchecked = SVGStringList -> JSM SVGStringList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGStringList -> JSM SVGStringList)
-> (JSVal -> SVGStringList) -> JSVal -> JSM SVGStringList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGStringList
SVGStringList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGStringList where
  makeObject :: SVGStringList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGStringList -> JSVal) -> SVGStringList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGStringList -> JSVal
unSVGStringList

instance IsGObject SVGStringList where
  typeGType :: SVGStringList -> JSM GType
typeGType SVGStringList
_ = JSM GType
gTypeSVGStringList
  {-# INLINE typeGType #-}

noSVGStringList :: Maybe SVGStringList
noSVGStringList :: Maybe SVGStringList
noSVGStringList = Maybe SVGStringList
forall a. Maybe a
Nothing
{-# INLINE noSVGStringList #-}

gTypeSVGStringList :: JSM GType
gTypeSVGStringList :: JSM GType
gTypeSVGStringList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGStringList"

-- | Functions for this inteface are in "JSDOM.SVGStyleElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGStyleElement Mozilla SVGStyleElement documentation>
newtype SVGStyleElement = SVGStyleElement { SVGStyleElement -> JSVal
unSVGStyleElement :: JSVal }

instance PToJSVal SVGStyleElement where
  pToJSVal :: SVGStyleElement -> JSVal
pToJSVal = SVGStyleElement -> JSVal
unSVGStyleElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGStyleElement where
  pFromJSVal :: JSVal -> SVGStyleElement
pFromJSVal = JSVal -> SVGStyleElement
SVGStyleElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGStyleElement where
  toJSVal :: SVGStyleElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGStyleElement -> JSVal) -> SVGStyleElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGStyleElement -> JSVal
unSVGStyleElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGStyleElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGStyleElement)
fromJSVal JSVal
v = (JSVal -> SVGStyleElement) -> Maybe JSVal -> Maybe SVGStyleElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGStyleElement
SVGStyleElement (Maybe JSVal -> Maybe SVGStyleElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGStyleElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGStyleElement
fromJSValUnchecked = SVGStyleElement -> JSM SVGStyleElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGStyleElement -> JSM SVGStyleElement)
-> (JSVal -> SVGStyleElement) -> JSVal -> JSM SVGStyleElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGStyleElement
SVGStyleElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGStyleElement where
  makeObject :: SVGStyleElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGStyleElement -> JSVal) -> SVGStyleElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGStyleElement -> JSVal
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 :: SVGStyleElement -> JSM GType
typeGType SVGStyleElement
_ = JSM GType
gTypeSVGStyleElement
  {-# INLINE typeGType #-}

noSVGStyleElement :: Maybe SVGStyleElement
noSVGStyleElement :: Maybe SVGStyleElement
noSVGStyleElement = Maybe SVGStyleElement
forall a. Maybe a
Nothing
{-# INLINE noSVGStyleElement #-}

gTypeSVGStyleElement :: JSM GType
gTypeSVGStyleElement :: JSM GType
gTypeSVGStyleElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGStyleElement"

-- | Functions for this inteface are in "JSDOM.SVGSwitchElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGSwitchElement Mozilla SVGSwitchElement documentation>
newtype SVGSwitchElement = SVGSwitchElement { SVGSwitchElement -> JSVal
unSVGSwitchElement :: JSVal }

instance PToJSVal SVGSwitchElement where
  pToJSVal :: SVGSwitchElement -> JSVal
pToJSVal = SVGSwitchElement -> JSVal
unSVGSwitchElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGSwitchElement where
  pFromJSVal :: JSVal -> SVGSwitchElement
pFromJSVal = JSVal -> SVGSwitchElement
SVGSwitchElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGSwitchElement where
  toJSVal :: SVGSwitchElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGSwitchElement -> JSVal) -> SVGSwitchElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGSwitchElement -> JSVal
unSVGSwitchElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGSwitchElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGSwitchElement)
fromJSVal JSVal
v = (JSVal -> SVGSwitchElement)
-> Maybe JSVal -> Maybe SVGSwitchElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGSwitchElement
SVGSwitchElement (Maybe JSVal -> Maybe SVGSwitchElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGSwitchElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGSwitchElement
fromJSValUnchecked = SVGSwitchElement -> JSM SVGSwitchElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGSwitchElement -> JSM SVGSwitchElement)
-> (JSVal -> SVGSwitchElement) -> JSVal -> JSM SVGSwitchElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGSwitchElement
SVGSwitchElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGSwitchElement where
  makeObject :: SVGSwitchElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGSwitchElement -> JSVal) -> SVGSwitchElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGSwitchElement -> JSVal
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 :: SVGSwitchElement -> JSM GType
typeGType SVGSwitchElement
_ = JSM GType
gTypeSVGSwitchElement
  {-# INLINE typeGType #-}

noSVGSwitchElement :: Maybe SVGSwitchElement
noSVGSwitchElement :: Maybe SVGSwitchElement
noSVGSwitchElement = Maybe SVGSwitchElement
forall a. Maybe a
Nothing
{-# INLINE noSVGSwitchElement #-}

gTypeSVGSwitchElement :: JSM GType
gTypeSVGSwitchElement :: JSM GType
gTypeSVGSwitchElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGSwitchElement"

-- | Functions for this inteface are in "JSDOM.SVGSymbolElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGFitToViewBox"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGSymbolElement Mozilla SVGSymbolElement documentation>
newtype SVGSymbolElement = SVGSymbolElement { SVGSymbolElement -> JSVal
unSVGSymbolElement :: JSVal }

instance PToJSVal SVGSymbolElement where
  pToJSVal :: SVGSymbolElement -> JSVal
pToJSVal = SVGSymbolElement -> JSVal
unSVGSymbolElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGSymbolElement where
  pFromJSVal :: JSVal -> SVGSymbolElement
pFromJSVal = JSVal -> SVGSymbolElement
SVGSymbolElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGSymbolElement where
  toJSVal :: SVGSymbolElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGSymbolElement -> JSVal) -> SVGSymbolElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGSymbolElement -> JSVal
unSVGSymbolElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGSymbolElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGSymbolElement)
fromJSVal JSVal
v = (JSVal -> SVGSymbolElement)
-> Maybe JSVal -> Maybe SVGSymbolElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGSymbolElement
SVGSymbolElement (Maybe JSVal -> Maybe SVGSymbolElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGSymbolElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGSymbolElement
fromJSValUnchecked = SVGSymbolElement -> JSM SVGSymbolElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGSymbolElement -> JSM SVGSymbolElement)
-> (JSVal -> SVGSymbolElement) -> JSVal -> JSM SVGSymbolElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGSymbolElement
SVGSymbolElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGSymbolElement where
  makeObject :: SVGSymbolElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGSymbolElement -> JSVal) -> SVGSymbolElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGSymbolElement -> JSVal
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 :: SVGSymbolElement -> JSM GType
typeGType SVGSymbolElement
_ = JSM GType
gTypeSVGSymbolElement
  {-# INLINE typeGType #-}

noSVGSymbolElement :: Maybe SVGSymbolElement
noSVGSymbolElement :: Maybe SVGSymbolElement
noSVGSymbolElement = Maybe SVGSymbolElement
forall a. Maybe a
Nothing
{-# INLINE noSVGSymbolElement #-}

gTypeSVGSymbolElement :: JSM GType
gTypeSVGSymbolElement :: JSM GType
gTypeSVGSymbolElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGSymbolElement"

-- | Functions for this inteface are in "JSDOM.SVGTRefElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGTextPositioningElement"
--     * "JSDOM.SVGTextContentElement"
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--     * "JSDOM.SVGURIReference"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGTRefElement Mozilla SVGTRefElement documentation>
newtype SVGTRefElement = SVGTRefElement { SVGTRefElement -> JSVal
unSVGTRefElement :: JSVal }

instance PToJSVal SVGTRefElement where
  pToJSVal :: SVGTRefElement -> JSVal
pToJSVal = SVGTRefElement -> JSVal
unSVGTRefElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGTRefElement where
  pFromJSVal :: JSVal -> SVGTRefElement
pFromJSVal = JSVal -> SVGTRefElement
SVGTRefElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGTRefElement where
  toJSVal :: SVGTRefElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGTRefElement -> JSVal) -> SVGTRefElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTRefElement -> JSVal
unSVGTRefElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGTRefElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGTRefElement)
fromJSVal JSVal
v = (JSVal -> SVGTRefElement) -> Maybe JSVal -> Maybe SVGTRefElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGTRefElement
SVGTRefElement (Maybe JSVal -> Maybe SVGTRefElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGTRefElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGTRefElement
fromJSValUnchecked = SVGTRefElement -> JSM SVGTRefElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGTRefElement -> JSM SVGTRefElement)
-> (JSVal -> SVGTRefElement) -> JSVal -> JSM SVGTRefElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGTRefElement
SVGTRefElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGTRefElement where
  makeObject :: SVGTRefElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGTRefElement -> JSVal) -> SVGTRefElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTRefElement -> JSVal
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 :: SVGTRefElement -> JSM GType
typeGType SVGTRefElement
_ = JSM GType
gTypeSVGTRefElement
  {-# INLINE typeGType #-}

noSVGTRefElement :: Maybe SVGTRefElement
noSVGTRefElement :: Maybe SVGTRefElement
noSVGTRefElement = Maybe SVGTRefElement
forall a. Maybe a
Nothing
{-# INLINE noSVGTRefElement #-}

gTypeSVGTRefElement :: JSM GType
gTypeSVGTRefElement :: JSM GType
gTypeSVGTRefElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGTRefElement"

-- | Functions for this inteface are in "JSDOM.SVGTSpanElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGTextPositioningElement"
--     * "JSDOM.SVGTextContentElement"
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGTSpanElement Mozilla SVGTSpanElement documentation>
newtype SVGTSpanElement = SVGTSpanElement { SVGTSpanElement -> JSVal
unSVGTSpanElement :: JSVal }

instance PToJSVal SVGTSpanElement where
  pToJSVal :: SVGTSpanElement -> JSVal
pToJSVal = SVGTSpanElement -> JSVal
unSVGTSpanElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGTSpanElement where
  pFromJSVal :: JSVal -> SVGTSpanElement
pFromJSVal = JSVal -> SVGTSpanElement
SVGTSpanElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGTSpanElement where
  toJSVal :: SVGTSpanElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGTSpanElement -> JSVal) -> SVGTSpanElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTSpanElement -> JSVal
unSVGTSpanElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGTSpanElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGTSpanElement)
fromJSVal JSVal
v = (JSVal -> SVGTSpanElement) -> Maybe JSVal -> Maybe SVGTSpanElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGTSpanElement
SVGTSpanElement (Maybe JSVal -> Maybe SVGTSpanElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGTSpanElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGTSpanElement
fromJSValUnchecked = SVGTSpanElement -> JSM SVGTSpanElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGTSpanElement -> JSM SVGTSpanElement)
-> (JSVal -> SVGTSpanElement) -> JSVal -> JSM SVGTSpanElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGTSpanElement
SVGTSpanElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGTSpanElement where
  makeObject :: SVGTSpanElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGTSpanElement -> JSVal) -> SVGTSpanElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTSpanElement -> JSVal
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 :: SVGTSpanElement -> JSM GType
typeGType SVGTSpanElement
_ = JSM GType
gTypeSVGTSpanElement
  {-# INLINE typeGType #-}

noSVGTSpanElement :: Maybe SVGTSpanElement
noSVGTSpanElement :: Maybe SVGTSpanElement
noSVGTSpanElement = Maybe SVGTSpanElement
forall a. Maybe a
Nothing
{-# INLINE noSVGTSpanElement #-}

gTypeSVGTSpanElement :: JSM GType
gTypeSVGTSpanElement :: JSM GType
gTypeSVGTSpanElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGTSpanElement"

-- | Functions for this inteface are in "JSDOM.SVGTests".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGTests Mozilla SVGTests documentation>
newtype SVGTests = SVGTests { SVGTests -> JSVal
unSVGTests :: JSVal }

instance PToJSVal SVGTests where
  pToJSVal :: SVGTests -> JSVal
pToJSVal = SVGTests -> JSVal
unSVGTests
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGTests where
  pFromJSVal :: JSVal -> SVGTests
pFromJSVal = JSVal -> SVGTests
SVGTests
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGTests where
  toJSVal :: SVGTests -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGTests -> JSVal) -> SVGTests -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTests -> JSVal
unSVGTests
  {-# INLINE toJSVal #-}

instance FromJSVal SVGTests where
  fromJSVal :: JSVal -> JSM (Maybe SVGTests)
fromJSVal JSVal
v = (JSVal -> SVGTests) -> Maybe JSVal -> Maybe SVGTests
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGTests
SVGTests (Maybe JSVal -> Maybe SVGTests)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGTests)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGTests
fromJSValUnchecked = SVGTests -> JSM SVGTests
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGTests -> JSM SVGTests)
-> (JSVal -> SVGTests) -> JSVal -> JSM SVGTests
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGTests
SVGTests
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGTests where
  makeObject :: SVGTests -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGTests -> JSVal) -> SVGTests -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTests -> JSVal
unSVGTests

class (IsGObject o) => IsSVGTests o
toSVGTests :: IsSVGTests o => o -> SVGTests
toSVGTests :: forall o. IsSVGTests o => o -> SVGTests
toSVGTests = JSVal -> SVGTests
SVGTests (JSVal -> SVGTests) -> (o -> JSVal) -> o -> SVGTests
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsSVGTests SVGTests
instance IsGObject SVGTests where
  typeGType :: SVGTests -> JSM GType
typeGType SVGTests
_ = JSM GType
gTypeSVGTests
  {-# INLINE typeGType #-}

noSVGTests :: Maybe SVGTests
noSVGTests :: Maybe SVGTests
noSVGTests = Maybe SVGTests
forall a. Maybe a
Nothing
{-# INLINE noSVGTests #-}

gTypeSVGTests :: JSM GType
gTypeSVGTests :: JSM GType
gTypeSVGTests = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGTests"

-- | Functions for this inteface are in "JSDOM.SVGTextContentElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGTextContentElement Mozilla SVGTextContentElement documentation>
newtype SVGTextContentElement = SVGTextContentElement { SVGTextContentElement -> JSVal
unSVGTextContentElement :: JSVal }

instance PToJSVal SVGTextContentElement where
  pToJSVal :: SVGTextContentElement -> JSVal
pToJSVal = SVGTextContentElement -> JSVal
unSVGTextContentElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGTextContentElement where
  pFromJSVal :: JSVal -> SVGTextContentElement
pFromJSVal = JSVal -> SVGTextContentElement
SVGTextContentElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGTextContentElement where
  toJSVal :: SVGTextContentElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGTextContentElement -> JSVal)
-> SVGTextContentElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTextContentElement -> JSVal
unSVGTextContentElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGTextContentElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGTextContentElement)
fromJSVal JSVal
v = (JSVal -> SVGTextContentElement)
-> Maybe JSVal -> Maybe SVGTextContentElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGTextContentElement
SVGTextContentElement (Maybe JSVal -> Maybe SVGTextContentElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGTextContentElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGTextContentElement
fromJSValUnchecked = SVGTextContentElement -> JSM SVGTextContentElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGTextContentElement -> JSM SVGTextContentElement)
-> (JSVal -> SVGTextContentElement)
-> JSVal
-> JSM SVGTextContentElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGTextContentElement
SVGTextContentElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGTextContentElement where
  makeObject :: SVGTextContentElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGTextContentElement -> JSVal)
-> SVGTextContentElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTextContentElement -> JSVal
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 :: forall o. IsSVGTextContentElement o => o -> SVGTextContentElement
toSVGTextContentElement = JSVal -> SVGTextContentElement
SVGTextContentElement (JSVal -> SVGTextContentElement)
-> (o -> JSVal) -> o -> SVGTextContentElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: SVGTextContentElement -> JSM GType
typeGType SVGTextContentElement
_ = JSM GType
gTypeSVGTextContentElement
  {-# INLINE typeGType #-}

noSVGTextContentElement :: Maybe SVGTextContentElement
noSVGTextContentElement :: Maybe SVGTextContentElement
noSVGTextContentElement = Maybe SVGTextContentElement
forall a. Maybe a
Nothing
{-# INLINE noSVGTextContentElement #-}

gTypeSVGTextContentElement :: JSM GType
gTypeSVGTextContentElement :: JSM GType
gTypeSVGTextContentElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGTextContentElement"

-- | Functions for this inteface are in "JSDOM.SVGTextElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGTextPositioningElement"
--     * "JSDOM.SVGTextContentElement"
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGTextElement Mozilla SVGTextElement documentation>
newtype SVGTextElement = SVGTextElement { SVGTextElement -> JSVal
unSVGTextElement :: JSVal }

instance PToJSVal SVGTextElement where
  pToJSVal :: SVGTextElement -> JSVal
pToJSVal = SVGTextElement -> JSVal
unSVGTextElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGTextElement where
  pFromJSVal :: JSVal -> SVGTextElement
pFromJSVal = JSVal -> SVGTextElement
SVGTextElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGTextElement where
  toJSVal :: SVGTextElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGTextElement -> JSVal) -> SVGTextElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTextElement -> JSVal
unSVGTextElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGTextElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGTextElement)
fromJSVal JSVal
v = (JSVal -> SVGTextElement) -> Maybe JSVal -> Maybe SVGTextElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGTextElement
SVGTextElement (Maybe JSVal -> Maybe SVGTextElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGTextElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGTextElement
fromJSValUnchecked = SVGTextElement -> JSM SVGTextElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGTextElement -> JSM SVGTextElement)
-> (JSVal -> SVGTextElement) -> JSVal -> JSM SVGTextElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGTextElement
SVGTextElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGTextElement where
  makeObject :: SVGTextElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGTextElement -> JSVal) -> SVGTextElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTextElement -> JSVal
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 :: SVGTextElement -> JSM GType
typeGType SVGTextElement
_ = JSM GType
gTypeSVGTextElement
  {-# INLINE typeGType #-}

noSVGTextElement :: Maybe SVGTextElement
noSVGTextElement :: Maybe SVGTextElement
noSVGTextElement = Maybe SVGTextElement
forall a. Maybe a
Nothing
{-# INLINE noSVGTextElement #-}

gTypeSVGTextElement :: JSM GType
gTypeSVGTextElement :: JSM GType
gTypeSVGTextElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGTextElement"

-- | Functions for this inteface are in "JSDOM.SVGTextPathElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGTextContentElement"
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--     * "JSDOM.SVGURIReference"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGTextPathElement Mozilla SVGTextPathElement documentation>
newtype SVGTextPathElement = SVGTextPathElement { SVGTextPathElement -> JSVal
unSVGTextPathElement :: JSVal }

instance PToJSVal SVGTextPathElement where
  pToJSVal :: SVGTextPathElement -> JSVal
pToJSVal = SVGTextPathElement -> JSVal
unSVGTextPathElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGTextPathElement where
  pFromJSVal :: JSVal -> SVGTextPathElement
pFromJSVal = JSVal -> SVGTextPathElement
SVGTextPathElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGTextPathElement where
  toJSVal :: SVGTextPathElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGTextPathElement -> JSVal) -> SVGTextPathElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTextPathElement -> JSVal
unSVGTextPathElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGTextPathElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGTextPathElement)
fromJSVal JSVal
v = (JSVal -> SVGTextPathElement)
-> Maybe JSVal -> Maybe SVGTextPathElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGTextPathElement
SVGTextPathElement (Maybe JSVal -> Maybe SVGTextPathElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGTextPathElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGTextPathElement
fromJSValUnchecked = SVGTextPathElement -> JSM SVGTextPathElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGTextPathElement -> JSM SVGTextPathElement)
-> (JSVal -> SVGTextPathElement) -> JSVal -> JSM SVGTextPathElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGTextPathElement
SVGTextPathElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGTextPathElement where
  makeObject :: SVGTextPathElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGTextPathElement -> JSVal)
-> SVGTextPathElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTextPathElement -> JSVal
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 :: SVGTextPathElement -> JSM GType
typeGType SVGTextPathElement
_ = JSM GType
gTypeSVGTextPathElement
  {-# INLINE typeGType #-}

noSVGTextPathElement :: Maybe SVGTextPathElement
noSVGTextPathElement :: Maybe SVGTextPathElement
noSVGTextPathElement = Maybe SVGTextPathElement
forall a. Maybe a
Nothing
{-# INLINE noSVGTextPathElement #-}

gTypeSVGTextPathElement :: JSM GType
gTypeSVGTextPathElement :: JSM GType
gTypeSVGTextPathElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGTextPathElement"

-- | Functions for this inteface are in "JSDOM.SVGTextPositioningElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGTextContentElement"
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGTextPositioningElement Mozilla SVGTextPositioningElement documentation>
newtype SVGTextPositioningElement = SVGTextPositioningElement { SVGTextPositioningElement -> JSVal
unSVGTextPositioningElement :: JSVal }

instance PToJSVal SVGTextPositioningElement where
  pToJSVal :: SVGTextPositioningElement -> JSVal
pToJSVal = SVGTextPositioningElement -> JSVal
unSVGTextPositioningElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGTextPositioningElement where
  pFromJSVal :: JSVal -> SVGTextPositioningElement
pFromJSVal = JSVal -> SVGTextPositioningElement
SVGTextPositioningElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGTextPositioningElement where
  toJSVal :: SVGTextPositioningElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGTextPositioningElement -> JSVal)
-> SVGTextPositioningElement
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTextPositioningElement -> JSVal
unSVGTextPositioningElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGTextPositioningElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGTextPositioningElement)
fromJSVal JSVal
v = (JSVal -> SVGTextPositioningElement)
-> Maybe JSVal -> Maybe SVGTextPositioningElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGTextPositioningElement
SVGTextPositioningElement (Maybe JSVal -> Maybe SVGTextPositioningElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGTextPositioningElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGTextPositioningElement
fromJSValUnchecked = SVGTextPositioningElement -> JSM SVGTextPositioningElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGTextPositioningElement -> JSM SVGTextPositioningElement)
-> (JSVal -> SVGTextPositioningElement)
-> JSVal
-> JSM SVGTextPositioningElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGTextPositioningElement
SVGTextPositioningElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGTextPositioningElement where
  makeObject :: SVGTextPositioningElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGTextPositioningElement -> JSVal)
-> SVGTextPositioningElement
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTextPositioningElement -> JSVal
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 :: forall o.
IsSVGTextPositioningElement o =>
o -> SVGTextPositioningElement
toSVGTextPositioningElement = JSVal -> SVGTextPositioningElement
SVGTextPositioningElement (JSVal -> SVGTextPositioningElement)
-> (o -> JSVal) -> o -> SVGTextPositioningElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: SVGTextPositioningElement -> JSM GType
typeGType SVGTextPositioningElement
_ = JSM GType
gTypeSVGTextPositioningElement
  {-# INLINE typeGType #-}

noSVGTextPositioningElement :: Maybe SVGTextPositioningElement
noSVGTextPositioningElement :: Maybe SVGTextPositioningElement
noSVGTextPositioningElement = Maybe SVGTextPositioningElement
forall a. Maybe a
Nothing
{-# INLINE noSVGTextPositioningElement #-}

gTypeSVGTextPositioningElement :: JSM GType
gTypeSVGTextPositioningElement :: JSM GType
gTypeSVGTextPositioningElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGTextPositioningElement"

-- | Functions for this inteface are in "JSDOM.SVGTitleElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGTitleElement Mozilla SVGTitleElement documentation>
newtype SVGTitleElement = SVGTitleElement { SVGTitleElement -> JSVal
unSVGTitleElement :: JSVal }

instance PToJSVal SVGTitleElement where
  pToJSVal :: SVGTitleElement -> JSVal
pToJSVal = SVGTitleElement -> JSVal
unSVGTitleElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGTitleElement where
  pFromJSVal :: JSVal -> SVGTitleElement
pFromJSVal = JSVal -> SVGTitleElement
SVGTitleElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGTitleElement where
  toJSVal :: SVGTitleElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGTitleElement -> JSVal) -> SVGTitleElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTitleElement -> JSVal
unSVGTitleElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGTitleElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGTitleElement)
fromJSVal JSVal
v = (JSVal -> SVGTitleElement) -> Maybe JSVal -> Maybe SVGTitleElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGTitleElement
SVGTitleElement (Maybe JSVal -> Maybe SVGTitleElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGTitleElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGTitleElement
fromJSValUnchecked = SVGTitleElement -> JSM SVGTitleElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGTitleElement -> JSM SVGTitleElement)
-> (JSVal -> SVGTitleElement) -> JSVal -> JSM SVGTitleElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGTitleElement
SVGTitleElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGTitleElement where
  makeObject :: SVGTitleElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGTitleElement -> JSVal) -> SVGTitleElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTitleElement -> JSVal
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 :: SVGTitleElement -> JSM GType
typeGType SVGTitleElement
_ = JSM GType
gTypeSVGTitleElement
  {-# INLINE typeGType #-}

noSVGTitleElement :: Maybe SVGTitleElement
noSVGTitleElement :: Maybe SVGTitleElement
noSVGTitleElement = Maybe SVGTitleElement
forall a. Maybe a
Nothing
{-# INLINE noSVGTitleElement #-}

gTypeSVGTitleElement :: JSM GType
gTypeSVGTitleElement :: JSM GType
gTypeSVGTitleElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGTitleElement"

-- | Functions for this inteface are in "JSDOM.SVGTransform".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGTransform Mozilla SVGTransform documentation>
newtype SVGTransform = SVGTransform { SVGTransform -> JSVal
unSVGTransform :: JSVal }

instance PToJSVal SVGTransform where
  pToJSVal :: SVGTransform -> JSVal
pToJSVal = SVGTransform -> JSVal
unSVGTransform
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGTransform where
  pFromJSVal :: JSVal -> SVGTransform
pFromJSVal = JSVal -> SVGTransform
SVGTransform
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGTransform where
  toJSVal :: SVGTransform -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGTransform -> JSVal) -> SVGTransform -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTransform -> JSVal
unSVGTransform
  {-# INLINE toJSVal #-}

instance FromJSVal SVGTransform where
  fromJSVal :: JSVal -> JSM (Maybe SVGTransform)
fromJSVal JSVal
v = (JSVal -> SVGTransform) -> Maybe JSVal -> Maybe SVGTransform
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGTransform
SVGTransform (Maybe JSVal -> Maybe SVGTransform)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGTransform)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGTransform
fromJSValUnchecked = SVGTransform -> JSM SVGTransform
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGTransform -> JSM SVGTransform)
-> (JSVal -> SVGTransform) -> JSVal -> JSM SVGTransform
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGTransform
SVGTransform
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGTransform where
  makeObject :: SVGTransform -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGTransform -> JSVal) -> SVGTransform -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTransform -> JSVal
unSVGTransform

instance IsGObject SVGTransform where
  typeGType :: SVGTransform -> JSM GType
typeGType SVGTransform
_ = JSM GType
gTypeSVGTransform
  {-# INLINE typeGType #-}

noSVGTransform :: Maybe SVGTransform
noSVGTransform :: Maybe SVGTransform
noSVGTransform = Maybe SVGTransform
forall a. Maybe a
Nothing
{-# INLINE noSVGTransform #-}

gTypeSVGTransform :: JSM GType
gTypeSVGTransform :: JSM GType
gTypeSVGTransform = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGTransform"

-- | Functions for this inteface are in "JSDOM.SVGTransformList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGTransformList Mozilla SVGTransformList documentation>
newtype SVGTransformList = SVGTransformList { SVGTransformList -> JSVal
unSVGTransformList :: JSVal }

instance PToJSVal SVGTransformList where
  pToJSVal :: SVGTransformList -> JSVal
pToJSVal = SVGTransformList -> JSVal
unSVGTransformList
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGTransformList where
  pFromJSVal :: JSVal -> SVGTransformList
pFromJSVal = JSVal -> SVGTransformList
SVGTransformList
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGTransformList where
  toJSVal :: SVGTransformList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGTransformList -> JSVal) -> SVGTransformList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTransformList -> JSVal
unSVGTransformList
  {-# INLINE toJSVal #-}

instance FromJSVal SVGTransformList where
  fromJSVal :: JSVal -> JSM (Maybe SVGTransformList)
fromJSVal JSVal
v = (JSVal -> SVGTransformList)
-> Maybe JSVal -> Maybe SVGTransformList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGTransformList
SVGTransformList (Maybe JSVal -> Maybe SVGTransformList)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGTransformList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGTransformList
fromJSValUnchecked = SVGTransformList -> JSM SVGTransformList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGTransformList -> JSM SVGTransformList)
-> (JSVal -> SVGTransformList) -> JSVal -> JSM SVGTransformList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGTransformList
SVGTransformList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGTransformList where
  makeObject :: SVGTransformList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGTransformList -> JSVal) -> SVGTransformList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGTransformList -> JSVal
unSVGTransformList

instance IsGObject SVGTransformList where
  typeGType :: SVGTransformList -> JSM GType
typeGType SVGTransformList
_ = JSM GType
gTypeSVGTransformList
  {-# INLINE typeGType #-}

noSVGTransformList :: Maybe SVGTransformList
noSVGTransformList :: Maybe SVGTransformList
noSVGTransformList = Maybe SVGTransformList
forall a. Maybe a
Nothing
{-# INLINE noSVGTransformList #-}

gTypeSVGTransformList :: JSM GType
gTypeSVGTransformList :: JSM GType
gTypeSVGTransformList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGTransformList"

-- | Functions for this inteface are in "JSDOM.SVGURIReference".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGURIReference Mozilla SVGURIReference documentation>
newtype SVGURIReference = SVGURIReference { SVGURIReference -> JSVal
unSVGURIReference :: JSVal }

instance PToJSVal SVGURIReference where
  pToJSVal :: SVGURIReference -> JSVal
pToJSVal = SVGURIReference -> JSVal
unSVGURIReference
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGURIReference where
  pFromJSVal :: JSVal -> SVGURIReference
pFromJSVal = JSVal -> SVGURIReference
SVGURIReference
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGURIReference where
  toJSVal :: SVGURIReference -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGURIReference -> JSVal) -> SVGURIReference -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGURIReference -> JSVal
unSVGURIReference
  {-# INLINE toJSVal #-}

instance FromJSVal SVGURIReference where
  fromJSVal :: JSVal -> JSM (Maybe SVGURIReference)
fromJSVal JSVal
v = (JSVal -> SVGURIReference) -> Maybe JSVal -> Maybe SVGURIReference
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGURIReference
SVGURIReference (Maybe JSVal -> Maybe SVGURIReference)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGURIReference)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGURIReference
fromJSValUnchecked = SVGURIReference -> JSM SVGURIReference
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGURIReference -> JSM SVGURIReference)
-> (JSVal -> SVGURIReference) -> JSVal -> JSM SVGURIReference
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGURIReference
SVGURIReference
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGURIReference where
  makeObject :: SVGURIReference -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGURIReference -> JSVal) -> SVGURIReference -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGURIReference -> JSVal
unSVGURIReference

class (IsGObject o) => IsSVGURIReference o
toSVGURIReference :: IsSVGURIReference o => o -> SVGURIReference
toSVGURIReference :: forall o. IsSVGURIReference o => o -> SVGURIReference
toSVGURIReference = JSVal -> SVGURIReference
SVGURIReference (JSVal -> SVGURIReference) -> (o -> JSVal) -> o -> SVGURIReference
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsSVGURIReference SVGURIReference
instance IsGObject SVGURIReference where
  typeGType :: SVGURIReference -> JSM GType
typeGType SVGURIReference
_ = JSM GType
gTypeSVGURIReference
  {-# INLINE typeGType #-}

noSVGURIReference :: Maybe SVGURIReference
noSVGURIReference :: Maybe SVGURIReference
noSVGURIReference = Maybe SVGURIReference
forall a. Maybe a
Nothing
{-# INLINE noSVGURIReference #-}

gTypeSVGURIReference :: JSM GType
gTypeSVGURIReference :: JSM GType
gTypeSVGURIReference = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGURIReference"

-- | Functions for this inteface are in "JSDOM.SVGUnitTypes".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGUnitTypes Mozilla SVGUnitTypes documentation>
newtype SVGUnitTypes = SVGUnitTypes { SVGUnitTypes -> JSVal
unSVGUnitTypes :: JSVal }

instance PToJSVal SVGUnitTypes where
  pToJSVal :: SVGUnitTypes -> JSVal
pToJSVal = SVGUnitTypes -> JSVal
unSVGUnitTypes
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGUnitTypes where
  pFromJSVal :: JSVal -> SVGUnitTypes
pFromJSVal = JSVal -> SVGUnitTypes
SVGUnitTypes
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGUnitTypes where
  toJSVal :: SVGUnitTypes -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGUnitTypes -> JSVal) -> SVGUnitTypes -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGUnitTypes -> JSVal
unSVGUnitTypes
  {-# INLINE toJSVal #-}

instance FromJSVal SVGUnitTypes where
  fromJSVal :: JSVal -> JSM (Maybe SVGUnitTypes)
fromJSVal JSVal
v = (JSVal -> SVGUnitTypes) -> Maybe JSVal -> Maybe SVGUnitTypes
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGUnitTypes
SVGUnitTypes (Maybe JSVal -> Maybe SVGUnitTypes)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGUnitTypes)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGUnitTypes
fromJSValUnchecked = SVGUnitTypes -> JSM SVGUnitTypes
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGUnitTypes -> JSM SVGUnitTypes)
-> (JSVal -> SVGUnitTypes) -> JSVal -> JSM SVGUnitTypes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGUnitTypes
SVGUnitTypes
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGUnitTypes where
  makeObject :: SVGUnitTypes -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGUnitTypes -> JSVal) -> SVGUnitTypes -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGUnitTypes -> JSVal
unSVGUnitTypes

instance IsGObject SVGUnitTypes where
  typeGType :: SVGUnitTypes -> JSM GType
typeGType SVGUnitTypes
_ = JSM GType
gTypeSVGUnitTypes
  {-# INLINE typeGType #-}

noSVGUnitTypes :: Maybe SVGUnitTypes
noSVGUnitTypes :: Maybe SVGUnitTypes
noSVGUnitTypes = Maybe SVGUnitTypes
forall a. Maybe a
Nothing
{-# INLINE noSVGUnitTypes #-}

gTypeSVGUnitTypes :: JSM GType
gTypeSVGUnitTypes :: JSM GType
gTypeSVGUnitTypes = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGUnitTypes"

-- | Functions for this inteface are in "JSDOM.SVGUseElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGGraphicsElement"
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGTests"
--     * "JSDOM.SVGURIReference"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGUseElement Mozilla SVGUseElement documentation>
newtype SVGUseElement = SVGUseElement { SVGUseElement -> JSVal
unSVGUseElement :: JSVal }

instance PToJSVal SVGUseElement where
  pToJSVal :: SVGUseElement -> JSVal
pToJSVal = SVGUseElement -> JSVal
unSVGUseElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGUseElement where
  pFromJSVal :: JSVal -> SVGUseElement
pFromJSVal = JSVal -> SVGUseElement
SVGUseElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGUseElement where
  toJSVal :: SVGUseElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGUseElement -> JSVal) -> SVGUseElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGUseElement -> JSVal
unSVGUseElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGUseElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGUseElement)
fromJSVal JSVal
v = (JSVal -> SVGUseElement) -> Maybe JSVal -> Maybe SVGUseElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGUseElement
SVGUseElement (Maybe JSVal -> Maybe SVGUseElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGUseElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGUseElement
fromJSValUnchecked = SVGUseElement -> JSM SVGUseElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGUseElement -> JSM SVGUseElement)
-> (JSVal -> SVGUseElement) -> JSVal -> JSM SVGUseElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGUseElement
SVGUseElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGUseElement where
  makeObject :: SVGUseElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGUseElement -> JSVal) -> SVGUseElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGUseElement -> JSVal
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 :: SVGUseElement -> JSM GType
typeGType SVGUseElement
_ = JSM GType
gTypeSVGUseElement
  {-# INLINE typeGType #-}

noSVGUseElement :: Maybe SVGUseElement
noSVGUseElement :: Maybe SVGUseElement
noSVGUseElement = Maybe SVGUseElement
forall a. Maybe a
Nothing
{-# INLINE noSVGUseElement #-}

gTypeSVGUseElement :: JSM GType
gTypeSVGUseElement :: JSM GType
gTypeSVGUseElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGUseElement"

-- | Functions for this inteface are in "JSDOM.SVGVKernElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGVKernElement Mozilla SVGVKernElement documentation>
newtype SVGVKernElement = SVGVKernElement { SVGVKernElement -> JSVal
unSVGVKernElement :: JSVal }

instance PToJSVal SVGVKernElement where
  pToJSVal :: SVGVKernElement -> JSVal
pToJSVal = SVGVKernElement -> JSVal
unSVGVKernElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGVKernElement where
  pFromJSVal :: JSVal -> SVGVKernElement
pFromJSVal = JSVal -> SVGVKernElement
SVGVKernElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGVKernElement where
  toJSVal :: SVGVKernElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGVKernElement -> JSVal) -> SVGVKernElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGVKernElement -> JSVal
unSVGVKernElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGVKernElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGVKernElement)
fromJSVal JSVal
v = (JSVal -> SVGVKernElement) -> Maybe JSVal -> Maybe SVGVKernElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGVKernElement
SVGVKernElement (Maybe JSVal -> Maybe SVGVKernElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGVKernElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGVKernElement
fromJSValUnchecked = SVGVKernElement -> JSM SVGVKernElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGVKernElement -> JSM SVGVKernElement)
-> (JSVal -> SVGVKernElement) -> JSVal -> JSM SVGVKernElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGVKernElement
SVGVKernElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGVKernElement where
  makeObject :: SVGVKernElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGVKernElement -> JSVal) -> SVGVKernElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGVKernElement -> JSVal
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 :: SVGVKernElement -> JSM GType
typeGType SVGVKernElement
_ = JSM GType
gTypeSVGVKernElement
  {-# INLINE typeGType #-}

noSVGVKernElement :: Maybe SVGVKernElement
noSVGVKernElement :: Maybe SVGVKernElement
noSVGVKernElement = Maybe SVGVKernElement
forall a. Maybe a
Nothing
{-# INLINE noSVGVKernElement #-}

gTypeSVGVKernElement :: JSM GType
gTypeSVGVKernElement :: JSM GType
gTypeSVGVKernElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGVKernElement"

-- | Functions for this inteface are in "JSDOM.SVGViewElement".
-- Base interface functions are in:
--
--     * "JSDOM.SVGElement"
--     * "JSDOM.Element"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.Slotable"
--     * "JSDOM.ParentNode"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Animatable"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.ElementCSSInlineStyle"
--     * "JSDOM.SVGZoomAndPan"
--     * "JSDOM.SVGFitToViewBox"
--     * "JSDOM.SVGExternalResourcesRequired"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGViewElement Mozilla SVGViewElement documentation>
newtype SVGViewElement = SVGViewElement { SVGViewElement -> JSVal
unSVGViewElement :: JSVal }

instance PToJSVal SVGViewElement where
  pToJSVal :: SVGViewElement -> JSVal
pToJSVal = SVGViewElement -> JSVal
unSVGViewElement
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGViewElement where
  pFromJSVal :: JSVal -> SVGViewElement
pFromJSVal = JSVal -> SVGViewElement
SVGViewElement
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGViewElement where
  toJSVal :: SVGViewElement -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGViewElement -> JSVal) -> SVGViewElement -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGViewElement -> JSVal
unSVGViewElement
  {-# INLINE toJSVal #-}

instance FromJSVal SVGViewElement where
  fromJSVal :: JSVal -> JSM (Maybe SVGViewElement)
fromJSVal JSVal
v = (JSVal -> SVGViewElement) -> Maybe JSVal -> Maybe SVGViewElement
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGViewElement
SVGViewElement (Maybe JSVal -> Maybe SVGViewElement)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGViewElement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGViewElement
fromJSValUnchecked = SVGViewElement -> JSM SVGViewElement
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGViewElement -> JSM SVGViewElement)
-> (JSVal -> SVGViewElement) -> JSVal -> JSM SVGViewElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGViewElement
SVGViewElement
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGViewElement where
  makeObject :: SVGViewElement -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGViewElement -> JSVal) -> SVGViewElement -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGViewElement -> JSVal
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 :: SVGViewElement -> JSM GType
typeGType SVGViewElement
_ = JSM GType
gTypeSVGViewElement
  {-# INLINE typeGType #-}

noSVGViewElement :: Maybe SVGViewElement
noSVGViewElement :: Maybe SVGViewElement
noSVGViewElement = Maybe SVGViewElement
forall a. Maybe a
Nothing
{-# INLINE noSVGViewElement #-}

gTypeSVGViewElement :: JSM GType
gTypeSVGViewElement :: JSM GType
gTypeSVGViewElement = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGViewElement"

-- | Functions for this inteface are in "JSDOM.SVGViewSpec".
-- Base interface functions are in:
--
--     * "JSDOM.SVGFitToViewBox"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGViewSpec Mozilla SVGViewSpec documentation>
newtype SVGViewSpec = SVGViewSpec { SVGViewSpec -> JSVal
unSVGViewSpec :: JSVal }

instance PToJSVal SVGViewSpec where
  pToJSVal :: SVGViewSpec -> JSVal
pToJSVal = SVGViewSpec -> JSVal
unSVGViewSpec
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGViewSpec where
  pFromJSVal :: JSVal -> SVGViewSpec
pFromJSVal = JSVal -> SVGViewSpec
SVGViewSpec
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGViewSpec where
  toJSVal :: SVGViewSpec -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGViewSpec -> JSVal) -> SVGViewSpec -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGViewSpec -> JSVal
unSVGViewSpec
  {-# INLINE toJSVal #-}

instance FromJSVal SVGViewSpec where
  fromJSVal :: JSVal -> JSM (Maybe SVGViewSpec)
fromJSVal JSVal
v = (JSVal -> SVGViewSpec) -> Maybe JSVal -> Maybe SVGViewSpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGViewSpec
SVGViewSpec (Maybe JSVal -> Maybe SVGViewSpec)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGViewSpec)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGViewSpec
fromJSValUnchecked = SVGViewSpec -> JSM SVGViewSpec
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGViewSpec -> JSM SVGViewSpec)
-> (JSVal -> SVGViewSpec) -> JSVal -> JSM SVGViewSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGViewSpec
SVGViewSpec
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGViewSpec where
  makeObject :: SVGViewSpec -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGViewSpec -> JSVal) -> SVGViewSpec -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGViewSpec -> JSVal
unSVGViewSpec

instance IsSVGFitToViewBox SVGViewSpec
instance IsGObject SVGViewSpec where
  typeGType :: SVGViewSpec -> JSM GType
typeGType SVGViewSpec
_ = JSM GType
gTypeSVGViewSpec
  {-# INLINE typeGType #-}

noSVGViewSpec :: Maybe SVGViewSpec
noSVGViewSpec :: Maybe SVGViewSpec
noSVGViewSpec = Maybe SVGViewSpec
forall a. Maybe a
Nothing
{-# INLINE noSVGViewSpec #-}

gTypeSVGViewSpec :: JSM GType
gTypeSVGViewSpec :: JSM GType
gTypeSVGViewSpec = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGViewSpec"

-- | Functions for this inteface are in "JSDOM.SVGZoomAndPan".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGZoomAndPan Mozilla SVGZoomAndPan documentation>
newtype SVGZoomAndPan = SVGZoomAndPan { SVGZoomAndPan -> JSVal
unSVGZoomAndPan :: JSVal }

instance PToJSVal SVGZoomAndPan where
  pToJSVal :: SVGZoomAndPan -> JSVal
pToJSVal = SVGZoomAndPan -> JSVal
unSVGZoomAndPan
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGZoomAndPan where
  pFromJSVal :: JSVal -> SVGZoomAndPan
pFromJSVal = JSVal -> SVGZoomAndPan
SVGZoomAndPan
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGZoomAndPan where
  toJSVal :: SVGZoomAndPan -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGZoomAndPan -> JSVal) -> SVGZoomAndPan -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGZoomAndPan -> JSVal
unSVGZoomAndPan
  {-# INLINE toJSVal #-}

instance FromJSVal SVGZoomAndPan where
  fromJSVal :: JSVal -> JSM (Maybe SVGZoomAndPan)
fromJSVal JSVal
v = (JSVal -> SVGZoomAndPan) -> Maybe JSVal -> Maybe SVGZoomAndPan
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGZoomAndPan
SVGZoomAndPan (Maybe JSVal -> Maybe SVGZoomAndPan)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGZoomAndPan)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGZoomAndPan
fromJSValUnchecked = SVGZoomAndPan -> JSM SVGZoomAndPan
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGZoomAndPan -> JSM SVGZoomAndPan)
-> (JSVal -> SVGZoomAndPan) -> JSVal -> JSM SVGZoomAndPan
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGZoomAndPan
SVGZoomAndPan
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGZoomAndPan where
  makeObject :: SVGZoomAndPan -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGZoomAndPan -> JSVal) -> SVGZoomAndPan -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGZoomAndPan -> JSVal
unSVGZoomAndPan

class (IsGObject o) => IsSVGZoomAndPan o
toSVGZoomAndPan :: IsSVGZoomAndPan o => o -> SVGZoomAndPan
toSVGZoomAndPan :: forall o. IsSVGZoomAndPan o => o -> SVGZoomAndPan
toSVGZoomAndPan = JSVal -> SVGZoomAndPan
SVGZoomAndPan (JSVal -> SVGZoomAndPan) -> (o -> JSVal) -> o -> SVGZoomAndPan
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsSVGZoomAndPan SVGZoomAndPan
instance IsGObject SVGZoomAndPan where
  typeGType :: SVGZoomAndPan -> JSM GType
typeGType SVGZoomAndPan
_ = JSM GType
gTypeSVGZoomAndPan
  {-# INLINE typeGType #-}

noSVGZoomAndPan :: Maybe SVGZoomAndPan
noSVGZoomAndPan :: Maybe SVGZoomAndPan
noSVGZoomAndPan = Maybe SVGZoomAndPan
forall a. Maybe a
Nothing
{-# INLINE noSVGZoomAndPan #-}

gTypeSVGZoomAndPan :: JSM GType
gTypeSVGZoomAndPan :: JSM GType
gTypeSVGZoomAndPan = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGZoomAndPan"

-- | Functions for this inteface are in "JSDOM.SVGZoomEvent".
-- Base interface functions are in:
--
--     * "JSDOM.UIEvent"
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SVGZoomEvent Mozilla SVGZoomEvent documentation>
newtype SVGZoomEvent = SVGZoomEvent { SVGZoomEvent -> JSVal
unSVGZoomEvent :: JSVal }

instance PToJSVal SVGZoomEvent where
  pToJSVal :: SVGZoomEvent -> JSVal
pToJSVal = SVGZoomEvent -> JSVal
unSVGZoomEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal SVGZoomEvent where
  pFromJSVal :: JSVal -> SVGZoomEvent
pFromJSVal = JSVal -> SVGZoomEvent
SVGZoomEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal SVGZoomEvent where
  toJSVal :: SVGZoomEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SVGZoomEvent -> JSVal) -> SVGZoomEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGZoomEvent -> JSVal
unSVGZoomEvent
  {-# INLINE toJSVal #-}

instance FromJSVal SVGZoomEvent where
  fromJSVal :: JSVal -> JSM (Maybe SVGZoomEvent)
fromJSVal JSVal
v = (JSVal -> SVGZoomEvent) -> Maybe JSVal -> Maybe SVGZoomEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SVGZoomEvent
SVGZoomEvent (Maybe JSVal -> Maybe SVGZoomEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe SVGZoomEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SVGZoomEvent
fromJSValUnchecked = SVGZoomEvent -> JSM SVGZoomEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SVGZoomEvent -> JSM SVGZoomEvent)
-> (JSVal -> SVGZoomEvent) -> JSVal -> JSM SVGZoomEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SVGZoomEvent
SVGZoomEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SVGZoomEvent where
  makeObject :: SVGZoomEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SVGZoomEvent -> JSVal) -> SVGZoomEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVGZoomEvent -> JSVal
unSVGZoomEvent

instance IsUIEvent SVGZoomEvent
instance IsEvent SVGZoomEvent
instance IsGObject SVGZoomEvent where
  typeGType :: SVGZoomEvent -> JSM GType
typeGType SVGZoomEvent
_ = JSM GType
gTypeSVGZoomEvent
  {-# INLINE typeGType #-}

noSVGZoomEvent :: Maybe SVGZoomEvent
noSVGZoomEvent :: Maybe SVGZoomEvent
noSVGZoomEvent = Maybe SVGZoomEvent
forall a. Maybe a
Nothing
{-# INLINE noSVGZoomEvent #-}

gTypeSVGZoomEvent :: JSM GType
gTypeSVGZoomEvent :: JSM GType
gTypeSVGZoomEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SVGZoomEvent"

-- | Functions for this inteface are in "JSDOM.Screen".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Screen Mozilla Screen documentation>
newtype Screen = Screen { Screen -> JSVal
unScreen :: JSVal }

instance PToJSVal Screen where
  pToJSVal :: Screen -> JSVal
pToJSVal = Screen -> JSVal
unScreen
  {-# INLINE pToJSVal #-}

instance PFromJSVal Screen where
  pFromJSVal :: JSVal -> Screen
pFromJSVal = JSVal -> Screen
Screen
  {-# INLINE pFromJSVal #-}

instance ToJSVal Screen where
  toJSVal :: Screen -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Screen -> JSVal) -> Screen -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Screen -> JSVal
unScreen
  {-# INLINE toJSVal #-}

instance FromJSVal Screen where
  fromJSVal :: JSVal -> JSM (Maybe Screen)
fromJSVal JSVal
v = (JSVal -> Screen) -> Maybe JSVal -> Maybe Screen
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Screen
Screen (Maybe JSVal -> Maybe Screen)
-> JSM (Maybe JSVal) -> JSM (Maybe Screen)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Screen
fromJSValUnchecked = Screen -> JSM Screen
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Screen -> JSM Screen) -> (JSVal -> Screen) -> JSVal -> JSM Screen
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Screen
Screen
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Screen where
  makeObject :: Screen -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Screen -> JSVal) -> Screen -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Screen -> JSVal
unScreen

instance IsGObject Screen where
  typeGType :: Screen -> JSM GType
typeGType Screen
_ = JSM GType
gTypeScreen
  {-# INLINE typeGType #-}

noScreen :: Maybe Screen
noScreen :: Maybe Screen
noScreen = Maybe Screen
forall a. Maybe a
Nothing
{-# INLINE noScreen #-}

gTypeScreen :: JSM GType
gTypeScreen :: JSM GType
gTypeScreen = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Screen"

-- | Functions for this inteface are in "JSDOM.ScriptProcessorNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ScriptProcessorNode Mozilla ScriptProcessorNode documentation>
newtype ScriptProcessorNode = ScriptProcessorNode { ScriptProcessorNode -> JSVal
unScriptProcessorNode :: JSVal }

instance PToJSVal ScriptProcessorNode where
  pToJSVal :: ScriptProcessorNode -> JSVal
pToJSVal = ScriptProcessorNode -> JSVal
unScriptProcessorNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal ScriptProcessorNode where
  pFromJSVal :: JSVal -> ScriptProcessorNode
pFromJSVal = JSVal -> ScriptProcessorNode
ScriptProcessorNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal ScriptProcessorNode where
  toJSVal :: ScriptProcessorNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ScriptProcessorNode -> JSVal)
-> ScriptProcessorNode
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptProcessorNode -> JSVal
unScriptProcessorNode
  {-# INLINE toJSVal #-}

instance FromJSVal ScriptProcessorNode where
  fromJSVal :: JSVal -> JSM (Maybe ScriptProcessorNode)
fromJSVal JSVal
v = (JSVal -> ScriptProcessorNode)
-> Maybe JSVal -> Maybe ScriptProcessorNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ScriptProcessorNode
ScriptProcessorNode (Maybe JSVal -> Maybe ScriptProcessorNode)
-> JSM (Maybe JSVal) -> JSM (Maybe ScriptProcessorNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ScriptProcessorNode
fromJSValUnchecked = ScriptProcessorNode -> JSM ScriptProcessorNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ScriptProcessorNode -> JSM ScriptProcessorNode)
-> (JSVal -> ScriptProcessorNode)
-> JSVal
-> JSM ScriptProcessorNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ScriptProcessorNode
ScriptProcessorNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ScriptProcessorNode where
  makeObject :: ScriptProcessorNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ScriptProcessorNode -> JSVal)
-> ScriptProcessorNode
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptProcessorNode -> JSVal
unScriptProcessorNode

instance IsAudioNode ScriptProcessorNode
instance IsEventTarget ScriptProcessorNode
instance IsGObject ScriptProcessorNode where
  typeGType :: ScriptProcessorNode -> JSM GType
typeGType ScriptProcessorNode
_ = JSM GType
gTypeScriptProcessorNode
  {-# INLINE typeGType #-}

noScriptProcessorNode :: Maybe ScriptProcessorNode
noScriptProcessorNode :: Maybe ScriptProcessorNode
noScriptProcessorNode = Maybe ScriptProcessorNode
forall a. Maybe a
Nothing
{-# INLINE noScriptProcessorNode #-}

gTypeScriptProcessorNode :: JSM GType
gTypeScriptProcessorNode :: JSM GType
gTypeScriptProcessorNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ScriptProcessorNode"

-- | Functions for this inteface are in "JSDOM.ScrollToOptions".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ScrollToOptions Mozilla ScrollToOptions documentation>
newtype ScrollToOptions = ScrollToOptions { ScrollToOptions -> JSVal
unScrollToOptions :: JSVal }

instance PToJSVal ScrollToOptions where
  pToJSVal :: ScrollToOptions -> JSVal
pToJSVal = ScrollToOptions -> JSVal
unScrollToOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal ScrollToOptions where
  pFromJSVal :: JSVal -> ScrollToOptions
pFromJSVal = JSVal -> ScrollToOptions
ScrollToOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal ScrollToOptions where
  toJSVal :: ScrollToOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ScrollToOptions -> JSVal) -> ScrollToOptions -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScrollToOptions -> JSVal
unScrollToOptions
  {-# INLINE toJSVal #-}

instance FromJSVal ScrollToOptions where
  fromJSVal :: JSVal -> JSM (Maybe ScrollToOptions)
fromJSVal JSVal
v = (JSVal -> ScrollToOptions) -> Maybe JSVal -> Maybe ScrollToOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ScrollToOptions
ScrollToOptions (Maybe JSVal -> Maybe ScrollToOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe ScrollToOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ScrollToOptions
fromJSValUnchecked = ScrollToOptions -> JSM ScrollToOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ScrollToOptions -> JSM ScrollToOptions)
-> (JSVal -> ScrollToOptions) -> JSVal -> JSM ScrollToOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ScrollToOptions
ScrollToOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ScrollToOptions where
  makeObject :: ScrollToOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ScrollToOptions -> JSVal) -> ScrollToOptions -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScrollToOptions -> JSVal
unScrollToOptions

instance IsGObject ScrollToOptions where
  typeGType :: ScrollToOptions -> JSM GType
typeGType ScrollToOptions
_ = JSM GType
gTypeScrollToOptions
  {-# INLINE typeGType #-}

noScrollToOptions :: Maybe ScrollToOptions
noScrollToOptions :: Maybe ScrollToOptions
noScrollToOptions = Maybe ScrollToOptions
forall a. Maybe a
Nothing
{-# INLINE noScrollToOptions #-}

gTypeScrollToOptions :: JSM GType
gTypeScrollToOptions :: JSM GType
gTypeScrollToOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ScrollToOptions"

-- | Functions for this inteface are in "JSDOM.SecurityPolicyViolationEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SecurityPolicyViolationEvent Mozilla SecurityPolicyViolationEvent documentation>
newtype SecurityPolicyViolationEvent = SecurityPolicyViolationEvent { SecurityPolicyViolationEvent -> JSVal
unSecurityPolicyViolationEvent :: JSVal }

instance PToJSVal SecurityPolicyViolationEvent where
  pToJSVal :: SecurityPolicyViolationEvent -> JSVal
pToJSVal = SecurityPolicyViolationEvent -> JSVal
unSecurityPolicyViolationEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal SecurityPolicyViolationEvent where
  pFromJSVal :: JSVal -> SecurityPolicyViolationEvent
pFromJSVal = JSVal -> SecurityPolicyViolationEvent
SecurityPolicyViolationEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal SecurityPolicyViolationEvent where
  toJSVal :: SecurityPolicyViolationEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SecurityPolicyViolationEvent -> JSVal)
-> SecurityPolicyViolationEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SecurityPolicyViolationEvent -> JSVal
unSecurityPolicyViolationEvent
  {-# INLINE toJSVal #-}

instance FromJSVal SecurityPolicyViolationEvent where
  fromJSVal :: JSVal -> JSM (Maybe SecurityPolicyViolationEvent)
fromJSVal JSVal
v = (JSVal -> SecurityPolicyViolationEvent)
-> Maybe JSVal -> Maybe SecurityPolicyViolationEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SecurityPolicyViolationEvent
SecurityPolicyViolationEvent (Maybe JSVal -> Maybe SecurityPolicyViolationEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe SecurityPolicyViolationEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SecurityPolicyViolationEvent
fromJSValUnchecked = SecurityPolicyViolationEvent -> JSM SecurityPolicyViolationEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SecurityPolicyViolationEvent -> JSM SecurityPolicyViolationEvent)
-> (JSVal -> SecurityPolicyViolationEvent)
-> JSVal
-> JSM SecurityPolicyViolationEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SecurityPolicyViolationEvent
SecurityPolicyViolationEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SecurityPolicyViolationEvent where
  makeObject :: SecurityPolicyViolationEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SecurityPolicyViolationEvent -> JSVal)
-> SecurityPolicyViolationEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SecurityPolicyViolationEvent -> JSVal
unSecurityPolicyViolationEvent

instance IsEvent SecurityPolicyViolationEvent
instance IsGObject SecurityPolicyViolationEvent where
  typeGType :: SecurityPolicyViolationEvent -> JSM GType
typeGType SecurityPolicyViolationEvent
_ = JSM GType
gTypeSecurityPolicyViolationEvent
  {-# INLINE typeGType #-}

noSecurityPolicyViolationEvent :: Maybe SecurityPolicyViolationEvent
noSecurityPolicyViolationEvent :: Maybe SecurityPolicyViolationEvent
noSecurityPolicyViolationEvent = Maybe SecurityPolicyViolationEvent
forall a. Maybe a
Nothing
{-# INLINE noSecurityPolicyViolationEvent #-}

gTypeSecurityPolicyViolationEvent :: JSM GType
gTypeSecurityPolicyViolationEvent :: JSM GType
gTypeSecurityPolicyViolationEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SecurityPolicyViolationEvent"

-- | Functions for this inteface are in "JSDOM.SecurityPolicyViolationEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SecurityPolicyViolationEventInit Mozilla SecurityPolicyViolationEventInit documentation>
newtype SecurityPolicyViolationEventInit = SecurityPolicyViolationEventInit { SecurityPolicyViolationEventInit -> JSVal
unSecurityPolicyViolationEventInit :: JSVal }

instance PToJSVal SecurityPolicyViolationEventInit where
  pToJSVal :: SecurityPolicyViolationEventInit -> JSVal
pToJSVal = SecurityPolicyViolationEventInit -> JSVal
unSecurityPolicyViolationEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal SecurityPolicyViolationEventInit where
  pFromJSVal :: JSVal -> SecurityPolicyViolationEventInit
pFromJSVal = JSVal -> SecurityPolicyViolationEventInit
SecurityPolicyViolationEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal SecurityPolicyViolationEventInit where
  toJSVal :: SecurityPolicyViolationEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SecurityPolicyViolationEventInit -> JSVal)
-> SecurityPolicyViolationEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SecurityPolicyViolationEventInit -> JSVal
unSecurityPolicyViolationEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal SecurityPolicyViolationEventInit where
  fromJSVal :: JSVal -> JSM (Maybe SecurityPolicyViolationEventInit)
fromJSVal JSVal
v = (JSVal -> SecurityPolicyViolationEventInit)
-> Maybe JSVal -> Maybe SecurityPolicyViolationEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SecurityPolicyViolationEventInit
SecurityPolicyViolationEventInit (Maybe JSVal -> Maybe SecurityPolicyViolationEventInit)
-> JSM (Maybe JSVal)
-> JSM (Maybe SecurityPolicyViolationEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SecurityPolicyViolationEventInit
fromJSValUnchecked = SecurityPolicyViolationEventInit
-> JSM SecurityPolicyViolationEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SecurityPolicyViolationEventInit
 -> JSM SecurityPolicyViolationEventInit)
-> (JSVal -> SecurityPolicyViolationEventInit)
-> JSVal
-> JSM SecurityPolicyViolationEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SecurityPolicyViolationEventInit
SecurityPolicyViolationEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SecurityPolicyViolationEventInit where
  makeObject :: SecurityPolicyViolationEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SecurityPolicyViolationEventInit -> JSVal)
-> SecurityPolicyViolationEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SecurityPolicyViolationEventInit -> JSVal
unSecurityPolicyViolationEventInit

instance IsEventInit SecurityPolicyViolationEventInit
instance IsGObject SecurityPolicyViolationEventInit where
  typeGType :: SecurityPolicyViolationEventInit -> JSM GType
typeGType SecurityPolicyViolationEventInit
_ = JSM GType
gTypeSecurityPolicyViolationEventInit
  {-# INLINE typeGType #-}

noSecurityPolicyViolationEventInit :: Maybe SecurityPolicyViolationEventInit
noSecurityPolicyViolationEventInit :: Maybe SecurityPolicyViolationEventInit
noSecurityPolicyViolationEventInit = Maybe SecurityPolicyViolationEventInit
forall a. Maybe a
Nothing
{-# INLINE noSecurityPolicyViolationEventInit #-}

gTypeSecurityPolicyViolationEventInit :: JSM GType
gTypeSecurityPolicyViolationEventInit :: JSM GType
gTypeSecurityPolicyViolationEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SecurityPolicyViolationEventInit"

-- | Functions for this inteface are in "JSDOM.Selection".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Selection Mozilla Selection documentation>
newtype Selection = Selection { Selection -> JSVal
unSelection :: JSVal }

instance PToJSVal Selection where
  pToJSVal :: Selection -> JSVal
pToJSVal = Selection -> JSVal
unSelection
  {-# INLINE pToJSVal #-}

instance PFromJSVal Selection where
  pFromJSVal :: JSVal -> Selection
pFromJSVal = JSVal -> Selection
Selection
  {-# INLINE pFromJSVal #-}

instance ToJSVal Selection where
  toJSVal :: Selection -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Selection -> JSVal) -> Selection -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Selection -> JSVal
unSelection
  {-# INLINE toJSVal #-}

instance FromJSVal Selection where
  fromJSVal :: JSVal -> JSM (Maybe Selection)
fromJSVal JSVal
v = (JSVal -> Selection) -> Maybe JSVal -> Maybe Selection
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Selection
Selection (Maybe JSVal -> Maybe Selection)
-> JSM (Maybe JSVal) -> JSM (Maybe Selection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Selection
fromJSValUnchecked = Selection -> JSM Selection
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Selection -> JSM Selection)
-> (JSVal -> Selection) -> JSVal -> JSM Selection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Selection
Selection
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Selection where
  makeObject :: Selection -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Selection -> JSVal) -> Selection -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Selection -> JSVal
unSelection

instance IsGObject Selection where
  typeGType :: Selection -> JSM GType
typeGType Selection
_ = JSM GType
gTypeSelection
  {-# INLINE typeGType #-}

noSelection :: Maybe Selection
noSelection :: Maybe Selection
noSelection = Maybe Selection
forall a. Maybe a
Nothing
{-# INLINE noSelection #-}

gTypeSelection :: JSM GType
gTypeSelection :: JSM GType
gTypeSelection = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Selection"

-- | Functions for this inteface are in "JSDOM.ShadowRoot".
-- Base interface functions are in:
--
--     * "JSDOM.DocumentFragment"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.NonElementParentNode"
--     * "JSDOM.ParentNode"
--     * "JSDOM.DocumentOrShadowRoot"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ShadowRoot Mozilla ShadowRoot documentation>
newtype ShadowRoot = ShadowRoot { ShadowRoot -> JSVal
unShadowRoot :: JSVal }

instance PToJSVal ShadowRoot where
  pToJSVal :: ShadowRoot -> JSVal
pToJSVal = ShadowRoot -> JSVal
unShadowRoot
  {-# INLINE pToJSVal #-}

instance PFromJSVal ShadowRoot where
  pFromJSVal :: JSVal -> ShadowRoot
pFromJSVal = JSVal -> ShadowRoot
ShadowRoot
  {-# INLINE pFromJSVal #-}

instance ToJSVal ShadowRoot where
  toJSVal :: ShadowRoot -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ShadowRoot -> JSVal) -> ShadowRoot -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShadowRoot -> JSVal
unShadowRoot
  {-# INLINE toJSVal #-}

instance FromJSVal ShadowRoot where
  fromJSVal :: JSVal -> JSM (Maybe ShadowRoot)
fromJSVal JSVal
v = (JSVal -> ShadowRoot) -> Maybe JSVal -> Maybe ShadowRoot
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ShadowRoot
ShadowRoot (Maybe JSVal -> Maybe ShadowRoot)
-> JSM (Maybe JSVal) -> JSM (Maybe ShadowRoot)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ShadowRoot
fromJSValUnchecked = ShadowRoot -> JSM ShadowRoot
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ShadowRoot -> JSM ShadowRoot)
-> (JSVal -> ShadowRoot) -> JSVal -> JSM ShadowRoot
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ShadowRoot
ShadowRoot
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ShadowRoot where
  makeObject :: ShadowRoot -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ShadowRoot -> JSVal) -> ShadowRoot -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShadowRoot -> JSVal
unShadowRoot

instance IsDocumentFragment ShadowRoot
instance IsNode ShadowRoot
instance IsEventTarget ShadowRoot
instance IsNonElementParentNode ShadowRoot
instance IsParentNode ShadowRoot
instance IsDocumentOrShadowRoot ShadowRoot
instance IsGObject ShadowRoot where
  typeGType :: ShadowRoot -> JSM GType
typeGType ShadowRoot
_ = JSM GType
gTypeShadowRoot
  {-# INLINE typeGType #-}

noShadowRoot :: Maybe ShadowRoot
noShadowRoot :: Maybe ShadowRoot
noShadowRoot = Maybe ShadowRoot
forall a. Maybe a
Nothing
{-# INLINE noShadowRoot #-}

gTypeShadowRoot :: JSM GType
gTypeShadowRoot :: JSM GType
gTypeShadowRoot = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ShadowRoot"

-- | Functions for this inteface are in "JSDOM.ShadowRootInit".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ShadowRootInit Mozilla ShadowRootInit documentation>
newtype ShadowRootInit = ShadowRootInit { ShadowRootInit -> JSVal
unShadowRootInit :: JSVal }

instance PToJSVal ShadowRootInit where
  pToJSVal :: ShadowRootInit -> JSVal
pToJSVal = ShadowRootInit -> JSVal
unShadowRootInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal ShadowRootInit where
  pFromJSVal :: JSVal -> ShadowRootInit
pFromJSVal = JSVal -> ShadowRootInit
ShadowRootInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal ShadowRootInit where
  toJSVal :: ShadowRootInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ShadowRootInit -> JSVal) -> ShadowRootInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShadowRootInit -> JSVal
unShadowRootInit
  {-# INLINE toJSVal #-}

instance FromJSVal ShadowRootInit where
  fromJSVal :: JSVal -> JSM (Maybe ShadowRootInit)
fromJSVal JSVal
v = (JSVal -> ShadowRootInit) -> Maybe JSVal -> Maybe ShadowRootInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ShadowRootInit
ShadowRootInit (Maybe JSVal -> Maybe ShadowRootInit)
-> JSM (Maybe JSVal) -> JSM (Maybe ShadowRootInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ShadowRootInit
fromJSValUnchecked = ShadowRootInit -> JSM ShadowRootInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ShadowRootInit -> JSM ShadowRootInit)
-> (JSVal -> ShadowRootInit) -> JSVal -> JSM ShadowRootInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ShadowRootInit
ShadowRootInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ShadowRootInit where
  makeObject :: ShadowRootInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ShadowRootInit -> JSVal) -> ShadowRootInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShadowRootInit -> JSVal
unShadowRootInit

instance IsGObject ShadowRootInit where
  typeGType :: ShadowRootInit -> JSM GType
typeGType ShadowRootInit
_ = JSM GType
gTypeShadowRootInit
  {-# INLINE typeGType #-}

noShadowRootInit :: Maybe ShadowRootInit
noShadowRootInit :: Maybe ShadowRootInit
noShadowRootInit = Maybe ShadowRootInit
forall a. Maybe a
Nothing
{-# INLINE noShadowRootInit #-}

gTypeShadowRootInit :: JSM GType
gTypeShadowRootInit :: JSM GType
gTypeShadowRootInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ShadowRootInit"

-- | Functions for this inteface are in "JSDOM.SiteBoundCredential".
-- Base interface functions are in:
--
--     * "JSDOM.BasicCredential"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SiteBoundCredential Mozilla SiteBoundCredential documentation>
newtype SiteBoundCredential = SiteBoundCredential { SiteBoundCredential -> JSVal
unSiteBoundCredential :: JSVal }

instance PToJSVal SiteBoundCredential where
  pToJSVal :: SiteBoundCredential -> JSVal
pToJSVal = SiteBoundCredential -> JSVal
unSiteBoundCredential
  {-# INLINE pToJSVal #-}

instance PFromJSVal SiteBoundCredential where
  pFromJSVal :: JSVal -> SiteBoundCredential
pFromJSVal = JSVal -> SiteBoundCredential
SiteBoundCredential
  {-# INLINE pFromJSVal #-}

instance ToJSVal SiteBoundCredential where
  toJSVal :: SiteBoundCredential -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SiteBoundCredential -> JSVal)
-> SiteBoundCredential
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SiteBoundCredential -> JSVal
unSiteBoundCredential
  {-# INLINE toJSVal #-}

instance FromJSVal SiteBoundCredential where
  fromJSVal :: JSVal -> JSM (Maybe SiteBoundCredential)
fromJSVal JSVal
v = (JSVal -> SiteBoundCredential)
-> Maybe JSVal -> Maybe SiteBoundCredential
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SiteBoundCredential
SiteBoundCredential (Maybe JSVal -> Maybe SiteBoundCredential)
-> JSM (Maybe JSVal) -> JSM (Maybe SiteBoundCredential)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SiteBoundCredential
fromJSValUnchecked = SiteBoundCredential -> JSM SiteBoundCredential
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SiteBoundCredential -> JSM SiteBoundCredential)
-> (JSVal -> SiteBoundCredential)
-> JSVal
-> JSM SiteBoundCredential
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SiteBoundCredential
SiteBoundCredential
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SiteBoundCredential where
  makeObject :: SiteBoundCredential -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SiteBoundCredential -> JSVal)
-> SiteBoundCredential
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SiteBoundCredential -> JSVal
unSiteBoundCredential

class (IsBasicCredential o, IsGObject o) => IsSiteBoundCredential o
toSiteBoundCredential :: IsSiteBoundCredential o => o -> SiteBoundCredential
toSiteBoundCredential :: forall o. IsSiteBoundCredential o => o -> SiteBoundCredential
toSiteBoundCredential = JSVal -> SiteBoundCredential
SiteBoundCredential (JSVal -> SiteBoundCredential)
-> (o -> JSVal) -> o -> SiteBoundCredential
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsSiteBoundCredential SiteBoundCredential
instance IsBasicCredential SiteBoundCredential
instance IsGObject SiteBoundCredential where
  typeGType :: SiteBoundCredential -> JSM GType
typeGType SiteBoundCredential
_ = JSM GType
gTypeSiteBoundCredential
  {-# INLINE typeGType #-}

noSiteBoundCredential :: Maybe SiteBoundCredential
noSiteBoundCredential :: Maybe SiteBoundCredential
noSiteBoundCredential = Maybe SiteBoundCredential
forall a. Maybe a
Nothing
{-# INLINE noSiteBoundCredential #-}

gTypeSiteBoundCredential :: JSM GType
gTypeSiteBoundCredential :: JSM GType
gTypeSiteBoundCredential = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SiteBoundCredential"

-- | Functions for this inteface are in "JSDOM.SiteBoundCredentialData".
-- Base interface functions are in:
--
--     * "JSDOM.CredentialData"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SiteBoundCredentialData Mozilla SiteBoundCredentialData documentation>
newtype SiteBoundCredentialData = SiteBoundCredentialData { SiteBoundCredentialData -> JSVal
unSiteBoundCredentialData :: JSVal }

instance PToJSVal SiteBoundCredentialData where
  pToJSVal :: SiteBoundCredentialData -> JSVal
pToJSVal = SiteBoundCredentialData -> JSVal
unSiteBoundCredentialData
  {-# INLINE pToJSVal #-}

instance PFromJSVal SiteBoundCredentialData where
  pFromJSVal :: JSVal -> SiteBoundCredentialData
pFromJSVal = JSVal -> SiteBoundCredentialData
SiteBoundCredentialData
  {-# INLINE pFromJSVal #-}

instance ToJSVal SiteBoundCredentialData where
  toJSVal :: SiteBoundCredentialData -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SiteBoundCredentialData -> JSVal)
-> SiteBoundCredentialData
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SiteBoundCredentialData -> JSVal
unSiteBoundCredentialData
  {-# INLINE toJSVal #-}

instance FromJSVal SiteBoundCredentialData where
  fromJSVal :: JSVal -> JSM (Maybe SiteBoundCredentialData)
fromJSVal JSVal
v = (JSVal -> SiteBoundCredentialData)
-> Maybe JSVal -> Maybe SiteBoundCredentialData
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SiteBoundCredentialData
SiteBoundCredentialData (Maybe JSVal -> Maybe SiteBoundCredentialData)
-> JSM (Maybe JSVal) -> JSM (Maybe SiteBoundCredentialData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SiteBoundCredentialData
fromJSValUnchecked = SiteBoundCredentialData -> JSM SiteBoundCredentialData
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SiteBoundCredentialData -> JSM SiteBoundCredentialData)
-> (JSVal -> SiteBoundCredentialData)
-> JSVal
-> JSM SiteBoundCredentialData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SiteBoundCredentialData
SiteBoundCredentialData
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SiteBoundCredentialData where
  makeObject :: SiteBoundCredentialData -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SiteBoundCredentialData -> JSVal)
-> SiteBoundCredentialData
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SiteBoundCredentialData -> JSVal
unSiteBoundCredentialData

class (IsCredentialData o, IsGObject o) => IsSiteBoundCredentialData o
toSiteBoundCredentialData :: IsSiteBoundCredentialData o => o -> SiteBoundCredentialData
toSiteBoundCredentialData :: forall o.
IsSiteBoundCredentialData o =>
o -> SiteBoundCredentialData
toSiteBoundCredentialData = JSVal -> SiteBoundCredentialData
SiteBoundCredentialData (JSVal -> SiteBoundCredentialData)
-> (o -> JSVal) -> o -> SiteBoundCredentialData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsSiteBoundCredentialData SiteBoundCredentialData
instance IsCredentialData SiteBoundCredentialData
instance IsGObject SiteBoundCredentialData where
  typeGType :: SiteBoundCredentialData -> JSM GType
typeGType SiteBoundCredentialData
_ = JSM GType
gTypeSiteBoundCredentialData
  {-# INLINE typeGType #-}

noSiteBoundCredentialData :: Maybe SiteBoundCredentialData
noSiteBoundCredentialData :: Maybe SiteBoundCredentialData
noSiteBoundCredentialData = Maybe SiteBoundCredentialData
forall a. Maybe a
Nothing
{-# INLINE noSiteBoundCredentialData #-}

gTypeSiteBoundCredentialData :: JSM GType
gTypeSiteBoundCredentialData :: JSM GType
gTypeSiteBoundCredentialData = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SiteBoundCredentialData"

-- | Functions for this inteface are in "JSDOM.Slotable".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Slotable Mozilla Slotable documentation>
newtype Slotable = Slotable { Slotable -> JSVal
unSlotable :: JSVal }

instance PToJSVal Slotable where
  pToJSVal :: Slotable -> JSVal
pToJSVal = Slotable -> JSVal
unSlotable
  {-# INLINE pToJSVal #-}

instance PFromJSVal Slotable where
  pFromJSVal :: JSVal -> Slotable
pFromJSVal = JSVal -> Slotable
Slotable
  {-# INLINE pFromJSVal #-}

instance ToJSVal Slotable where
  toJSVal :: Slotable -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (Slotable -> JSVal) -> Slotable -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Slotable -> JSVal
unSlotable
  {-# INLINE toJSVal #-}

instance FromJSVal Slotable where
  fromJSVal :: JSVal -> JSM (Maybe Slotable)
fromJSVal JSVal
v = (JSVal -> Slotable) -> Maybe JSVal -> Maybe Slotable
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Slotable
Slotable (Maybe JSVal -> Maybe Slotable)
-> JSM (Maybe JSVal) -> JSM (Maybe Slotable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Slotable
fromJSValUnchecked = Slotable -> JSM Slotable
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Slotable -> JSM Slotable)
-> (JSVal -> Slotable) -> JSVal -> JSM Slotable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Slotable
Slotable
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Slotable where
  makeObject :: Slotable -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Slotable -> JSVal) -> Slotable -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Slotable -> JSVal
unSlotable

class (IsGObject o) => IsSlotable o
toSlotable :: IsSlotable o => o -> Slotable
toSlotable :: forall o. IsSlotable o => o -> Slotable
toSlotable = JSVal -> Slotable
Slotable (JSVal -> Slotable) -> (o -> JSVal) -> o -> Slotable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsSlotable Slotable
instance IsGObject Slotable where
  typeGType :: Slotable -> JSM GType
typeGType Slotable
_ = JSM GType
gTypeSlotable
  {-# INLINE typeGType #-}

noSlotable :: Maybe Slotable
noSlotable :: Maybe Slotable
noSlotable = Maybe Slotable
forall a. Maybe a
Nothing
{-# INLINE noSlotable #-}

gTypeSlotable :: JSM GType
gTypeSlotable :: JSM GType
gTypeSlotable = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Slotable"

-- | Functions for this inteface are in "JSDOM.SourceBuffer".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SourceBuffer Mozilla SourceBuffer documentation>
newtype SourceBuffer = SourceBuffer { SourceBuffer -> JSVal
unSourceBuffer :: JSVal }

instance PToJSVal SourceBuffer where
  pToJSVal :: SourceBuffer -> JSVal
pToJSVal = SourceBuffer -> JSVal
unSourceBuffer
  {-# INLINE pToJSVal #-}

instance PFromJSVal SourceBuffer where
  pFromJSVal :: JSVal -> SourceBuffer
pFromJSVal = JSVal -> SourceBuffer
SourceBuffer
  {-# INLINE pFromJSVal #-}

instance ToJSVal SourceBuffer where
  toJSVal :: SourceBuffer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SourceBuffer -> JSVal) -> SourceBuffer -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceBuffer -> JSVal
unSourceBuffer
  {-# INLINE toJSVal #-}

instance FromJSVal SourceBuffer where
  fromJSVal :: JSVal -> JSM (Maybe SourceBuffer)
fromJSVal JSVal
v = (JSVal -> SourceBuffer) -> Maybe JSVal -> Maybe SourceBuffer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SourceBuffer
SourceBuffer (Maybe JSVal -> Maybe SourceBuffer)
-> JSM (Maybe JSVal) -> JSM (Maybe SourceBuffer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SourceBuffer
fromJSValUnchecked = SourceBuffer -> JSM SourceBuffer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceBuffer -> JSM SourceBuffer)
-> (JSVal -> SourceBuffer) -> JSVal -> JSM SourceBuffer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SourceBuffer
SourceBuffer
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SourceBuffer where
  makeObject :: SourceBuffer -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SourceBuffer -> JSVal) -> SourceBuffer -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceBuffer -> JSVal
unSourceBuffer

instance IsEventTarget SourceBuffer
instance IsGObject SourceBuffer where
  typeGType :: SourceBuffer -> JSM GType
typeGType SourceBuffer
_ = JSM GType
gTypeSourceBuffer
  {-# INLINE typeGType #-}

noSourceBuffer :: Maybe SourceBuffer
noSourceBuffer :: Maybe SourceBuffer
noSourceBuffer = Maybe SourceBuffer
forall a. Maybe a
Nothing
{-# INLINE noSourceBuffer #-}

gTypeSourceBuffer :: JSM GType
gTypeSourceBuffer :: JSM GType
gTypeSourceBuffer = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SourceBuffer"

-- | Functions for this inteface are in "JSDOM.SourceBufferList".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SourceBufferList Mozilla SourceBufferList documentation>
newtype SourceBufferList = SourceBufferList { SourceBufferList -> JSVal
unSourceBufferList :: JSVal }

instance PToJSVal SourceBufferList where
  pToJSVal :: SourceBufferList -> JSVal
pToJSVal = SourceBufferList -> JSVal
unSourceBufferList
  {-# INLINE pToJSVal #-}

instance PFromJSVal SourceBufferList where
  pFromJSVal :: JSVal -> SourceBufferList
pFromJSVal = JSVal -> SourceBufferList
SourceBufferList
  {-# INLINE pFromJSVal #-}

instance ToJSVal SourceBufferList where
  toJSVal :: SourceBufferList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SourceBufferList -> JSVal) -> SourceBufferList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceBufferList -> JSVal
unSourceBufferList
  {-# INLINE toJSVal #-}

instance FromJSVal SourceBufferList where
  fromJSVal :: JSVal -> JSM (Maybe SourceBufferList)
fromJSVal JSVal
v = (JSVal -> SourceBufferList)
-> Maybe JSVal -> Maybe SourceBufferList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SourceBufferList
SourceBufferList (Maybe JSVal -> Maybe SourceBufferList)
-> JSM (Maybe JSVal) -> JSM (Maybe SourceBufferList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SourceBufferList
fromJSValUnchecked = SourceBufferList -> JSM SourceBufferList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceBufferList -> JSM SourceBufferList)
-> (JSVal -> SourceBufferList) -> JSVal -> JSM SourceBufferList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SourceBufferList
SourceBufferList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SourceBufferList where
  makeObject :: SourceBufferList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SourceBufferList -> JSVal) -> SourceBufferList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceBufferList -> JSVal
unSourceBufferList

instance IsEventTarget SourceBufferList
instance IsGObject SourceBufferList where
  typeGType :: SourceBufferList -> JSM GType
typeGType SourceBufferList
_ = JSM GType
gTypeSourceBufferList
  {-# INLINE typeGType #-}

noSourceBufferList :: Maybe SourceBufferList
noSourceBufferList :: Maybe SourceBufferList
noSourceBufferList = Maybe SourceBufferList
forall a. Maybe a
Nothing
{-# INLINE noSourceBufferList #-}

gTypeSourceBufferList :: JSM GType
gTypeSourceBufferList :: JSM GType
gTypeSourceBufferList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SourceBufferList"

-- | Functions for this inteface are in "JSDOM.SpeechSynthesis".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SpeechSynthesis Mozilla SpeechSynthesis documentation>
newtype SpeechSynthesis = SpeechSynthesis { SpeechSynthesis -> JSVal
unSpeechSynthesis :: JSVal }

instance PToJSVal SpeechSynthesis where
  pToJSVal :: SpeechSynthesis -> JSVal
pToJSVal = SpeechSynthesis -> JSVal
unSpeechSynthesis
  {-# INLINE pToJSVal #-}

instance PFromJSVal SpeechSynthesis where
  pFromJSVal :: JSVal -> SpeechSynthesis
pFromJSVal = JSVal -> SpeechSynthesis
SpeechSynthesis
  {-# INLINE pFromJSVal #-}

instance ToJSVal SpeechSynthesis where
  toJSVal :: SpeechSynthesis -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SpeechSynthesis -> JSVal) -> SpeechSynthesis -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpeechSynthesis -> JSVal
unSpeechSynthesis
  {-# INLINE toJSVal #-}

instance FromJSVal SpeechSynthesis where
  fromJSVal :: JSVal -> JSM (Maybe SpeechSynthesis)
fromJSVal JSVal
v = (JSVal -> SpeechSynthesis) -> Maybe JSVal -> Maybe SpeechSynthesis
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SpeechSynthesis
SpeechSynthesis (Maybe JSVal -> Maybe SpeechSynthesis)
-> JSM (Maybe JSVal) -> JSM (Maybe SpeechSynthesis)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SpeechSynthesis
fromJSValUnchecked = SpeechSynthesis -> JSM SpeechSynthesis
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SpeechSynthesis -> JSM SpeechSynthesis)
-> (JSVal -> SpeechSynthesis) -> JSVal -> JSM SpeechSynthesis
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SpeechSynthesis
SpeechSynthesis
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SpeechSynthesis where
  makeObject :: SpeechSynthesis -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SpeechSynthesis -> JSVal) -> SpeechSynthesis -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpeechSynthesis -> JSVal
unSpeechSynthesis

instance IsGObject SpeechSynthesis where
  typeGType :: SpeechSynthesis -> JSM GType
typeGType SpeechSynthesis
_ = JSM GType
gTypeSpeechSynthesis
  {-# INLINE typeGType #-}

noSpeechSynthesis :: Maybe SpeechSynthesis
noSpeechSynthesis :: Maybe SpeechSynthesis
noSpeechSynthesis = Maybe SpeechSynthesis
forall a. Maybe a
Nothing
{-# INLINE noSpeechSynthesis #-}

gTypeSpeechSynthesis :: JSM GType
gTypeSpeechSynthesis :: JSM GType
gTypeSpeechSynthesis = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SpeechSynthesis"

-- | Functions for this inteface are in "JSDOM.SpeechSynthesisEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SpeechSynthesisEvent Mozilla SpeechSynthesisEvent documentation>
newtype SpeechSynthesisEvent = SpeechSynthesisEvent { SpeechSynthesisEvent -> JSVal
unSpeechSynthesisEvent :: JSVal }

instance PToJSVal SpeechSynthesisEvent where
  pToJSVal :: SpeechSynthesisEvent -> JSVal
pToJSVal = SpeechSynthesisEvent -> JSVal
unSpeechSynthesisEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal SpeechSynthesisEvent where
  pFromJSVal :: JSVal -> SpeechSynthesisEvent
pFromJSVal = JSVal -> SpeechSynthesisEvent
SpeechSynthesisEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal SpeechSynthesisEvent where
  toJSVal :: SpeechSynthesisEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SpeechSynthesisEvent -> JSVal)
-> SpeechSynthesisEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpeechSynthesisEvent -> JSVal
unSpeechSynthesisEvent
  {-# INLINE toJSVal #-}

instance FromJSVal SpeechSynthesisEvent where
  fromJSVal :: JSVal -> JSM (Maybe SpeechSynthesisEvent)
fromJSVal JSVal
v = (JSVal -> SpeechSynthesisEvent)
-> Maybe JSVal -> Maybe SpeechSynthesisEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SpeechSynthesisEvent
SpeechSynthesisEvent (Maybe JSVal -> Maybe SpeechSynthesisEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe SpeechSynthesisEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SpeechSynthesisEvent
fromJSValUnchecked = SpeechSynthesisEvent -> JSM SpeechSynthesisEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SpeechSynthesisEvent -> JSM SpeechSynthesisEvent)
-> (JSVal -> SpeechSynthesisEvent)
-> JSVal
-> JSM SpeechSynthesisEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SpeechSynthesisEvent
SpeechSynthesisEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SpeechSynthesisEvent where
  makeObject :: SpeechSynthesisEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SpeechSynthesisEvent -> JSVal)
-> SpeechSynthesisEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpeechSynthesisEvent -> JSVal
unSpeechSynthesisEvent

instance IsEvent SpeechSynthesisEvent
instance IsGObject SpeechSynthesisEvent where
  typeGType :: SpeechSynthesisEvent -> JSM GType
typeGType SpeechSynthesisEvent
_ = JSM GType
gTypeSpeechSynthesisEvent
  {-# INLINE typeGType #-}

noSpeechSynthesisEvent :: Maybe SpeechSynthesisEvent
noSpeechSynthesisEvent :: Maybe SpeechSynthesisEvent
noSpeechSynthesisEvent = Maybe SpeechSynthesisEvent
forall a. Maybe a
Nothing
{-# INLINE noSpeechSynthesisEvent #-}

gTypeSpeechSynthesisEvent :: JSM GType
gTypeSpeechSynthesisEvent :: JSM GType
gTypeSpeechSynthesisEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SpeechSynthesisEvent"

-- | Functions for this inteface are in "JSDOM.SpeechSynthesisUtterance".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SpeechSynthesisUtterance Mozilla SpeechSynthesisUtterance documentation>
newtype SpeechSynthesisUtterance = SpeechSynthesisUtterance { SpeechSynthesisUtterance -> JSVal
unSpeechSynthesisUtterance :: JSVal }

instance PToJSVal SpeechSynthesisUtterance where
  pToJSVal :: SpeechSynthesisUtterance -> JSVal
pToJSVal = SpeechSynthesisUtterance -> JSVal
unSpeechSynthesisUtterance
  {-# INLINE pToJSVal #-}

instance PFromJSVal SpeechSynthesisUtterance where
  pFromJSVal :: JSVal -> SpeechSynthesisUtterance
pFromJSVal = JSVal -> SpeechSynthesisUtterance
SpeechSynthesisUtterance
  {-# INLINE pFromJSVal #-}

instance ToJSVal SpeechSynthesisUtterance where
  toJSVal :: SpeechSynthesisUtterance -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SpeechSynthesisUtterance -> JSVal)
-> SpeechSynthesisUtterance
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpeechSynthesisUtterance -> JSVal
unSpeechSynthesisUtterance
  {-# INLINE toJSVal #-}

instance FromJSVal SpeechSynthesisUtterance where
  fromJSVal :: JSVal -> JSM (Maybe SpeechSynthesisUtterance)
fromJSVal JSVal
v = (JSVal -> SpeechSynthesisUtterance)
-> Maybe JSVal -> Maybe SpeechSynthesisUtterance
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SpeechSynthesisUtterance
SpeechSynthesisUtterance (Maybe JSVal -> Maybe SpeechSynthesisUtterance)
-> JSM (Maybe JSVal) -> JSM (Maybe SpeechSynthesisUtterance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SpeechSynthesisUtterance
fromJSValUnchecked = SpeechSynthesisUtterance -> JSM SpeechSynthesisUtterance
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SpeechSynthesisUtterance -> JSM SpeechSynthesisUtterance)
-> (JSVal -> SpeechSynthesisUtterance)
-> JSVal
-> JSM SpeechSynthesisUtterance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SpeechSynthesisUtterance
SpeechSynthesisUtterance
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SpeechSynthesisUtterance where
  makeObject :: SpeechSynthesisUtterance -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SpeechSynthesisUtterance -> JSVal)
-> SpeechSynthesisUtterance
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpeechSynthesisUtterance -> JSVal
unSpeechSynthesisUtterance

instance IsEventTarget SpeechSynthesisUtterance
instance IsGObject SpeechSynthesisUtterance where
  typeGType :: SpeechSynthesisUtterance -> JSM GType
typeGType SpeechSynthesisUtterance
_ = JSM GType
gTypeSpeechSynthesisUtterance
  {-# INLINE typeGType #-}

noSpeechSynthesisUtterance :: Maybe SpeechSynthesisUtterance
noSpeechSynthesisUtterance :: Maybe SpeechSynthesisUtterance
noSpeechSynthesisUtterance = Maybe SpeechSynthesisUtterance
forall a. Maybe a
Nothing
{-# INLINE noSpeechSynthesisUtterance #-}

gTypeSpeechSynthesisUtterance :: JSM GType
gTypeSpeechSynthesisUtterance :: JSM GType
gTypeSpeechSynthesisUtterance = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SpeechSynthesisUtterance"

-- | Functions for this inteface are in "JSDOM.SpeechSynthesisVoice".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/SpeechSynthesisVoice Mozilla SpeechSynthesisVoice documentation>
newtype SpeechSynthesisVoice = SpeechSynthesisVoice { SpeechSynthesisVoice -> JSVal
unSpeechSynthesisVoice :: JSVal }

instance PToJSVal SpeechSynthesisVoice where
  pToJSVal :: SpeechSynthesisVoice -> JSVal
pToJSVal = SpeechSynthesisVoice -> JSVal
unSpeechSynthesisVoice
  {-# INLINE pToJSVal #-}

instance PFromJSVal SpeechSynthesisVoice where
  pFromJSVal :: JSVal -> SpeechSynthesisVoice
pFromJSVal = JSVal -> SpeechSynthesisVoice
SpeechSynthesisVoice
  {-# INLINE pFromJSVal #-}

instance ToJSVal SpeechSynthesisVoice where
  toJSVal :: SpeechSynthesisVoice -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SpeechSynthesisVoice -> JSVal)
-> SpeechSynthesisVoice
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpeechSynthesisVoice -> JSVal
unSpeechSynthesisVoice
  {-# INLINE toJSVal #-}

instance FromJSVal SpeechSynthesisVoice where
  fromJSVal :: JSVal -> JSM (Maybe SpeechSynthesisVoice)
fromJSVal JSVal
v = (JSVal -> SpeechSynthesisVoice)
-> Maybe JSVal -> Maybe SpeechSynthesisVoice
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SpeechSynthesisVoice
SpeechSynthesisVoice (Maybe JSVal -> Maybe SpeechSynthesisVoice)
-> JSM (Maybe JSVal) -> JSM (Maybe SpeechSynthesisVoice)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SpeechSynthesisVoice
fromJSValUnchecked = SpeechSynthesisVoice -> JSM SpeechSynthesisVoice
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SpeechSynthesisVoice -> JSM SpeechSynthesisVoice)
-> (JSVal -> SpeechSynthesisVoice)
-> JSVal
-> JSM SpeechSynthesisVoice
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SpeechSynthesisVoice
SpeechSynthesisVoice
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SpeechSynthesisVoice where
  makeObject :: SpeechSynthesisVoice -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SpeechSynthesisVoice -> JSVal)
-> SpeechSynthesisVoice
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpeechSynthesisVoice -> JSVal
unSpeechSynthesisVoice

instance IsGObject SpeechSynthesisVoice where
  typeGType :: SpeechSynthesisVoice -> JSM GType
typeGType SpeechSynthesisVoice
_ = JSM GType
gTypeSpeechSynthesisVoice
  {-# INLINE typeGType #-}

noSpeechSynthesisVoice :: Maybe SpeechSynthesisVoice
noSpeechSynthesisVoice :: Maybe SpeechSynthesisVoice
noSpeechSynthesisVoice = Maybe SpeechSynthesisVoice
forall a. Maybe a
Nothing
{-# INLINE noSpeechSynthesisVoice #-}

gTypeSpeechSynthesisVoice :: JSM GType
gTypeSpeechSynthesisVoice :: JSM GType
gTypeSpeechSynthesisVoice = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"SpeechSynthesisVoice"

-- | Functions for this inteface are in "JSDOM.StaticRange".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/StaticRange Mozilla StaticRange documentation>
newtype StaticRange = StaticRange { StaticRange -> JSVal
unStaticRange :: JSVal }

instance PToJSVal StaticRange where
  pToJSVal :: StaticRange -> JSVal
pToJSVal = StaticRange -> JSVal
unStaticRange
  {-# INLINE pToJSVal #-}

instance PFromJSVal StaticRange where
  pFromJSVal :: JSVal -> StaticRange
pFromJSVal = JSVal -> StaticRange
StaticRange
  {-# INLINE pFromJSVal #-}

instance ToJSVal StaticRange where
  toJSVal :: StaticRange -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (StaticRange -> JSVal) -> StaticRange -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StaticRange -> JSVal
unStaticRange
  {-# INLINE toJSVal #-}

instance FromJSVal StaticRange where
  fromJSVal :: JSVal -> JSM (Maybe StaticRange)
fromJSVal JSVal
v = (JSVal -> StaticRange) -> Maybe JSVal -> Maybe StaticRange
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> StaticRange
StaticRange (Maybe JSVal -> Maybe StaticRange)
-> JSM (Maybe JSVal) -> JSM (Maybe StaticRange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM StaticRange
fromJSValUnchecked = StaticRange -> JSM StaticRange
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (StaticRange -> JSM StaticRange)
-> (JSVal -> StaticRange) -> JSVal -> JSM StaticRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> StaticRange
StaticRange
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject StaticRange where
  makeObject :: StaticRange -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (StaticRange -> JSVal) -> StaticRange -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StaticRange -> JSVal
unStaticRange

instance IsGObject StaticRange where
  typeGType :: StaticRange -> JSM GType
typeGType StaticRange
_ = JSM GType
gTypeStaticRange
  {-# INLINE typeGType #-}

noStaticRange :: Maybe StaticRange
noStaticRange :: Maybe StaticRange
noStaticRange = Maybe StaticRange
forall a. Maybe a
Nothing
{-# INLINE noStaticRange #-}

gTypeStaticRange :: JSM GType
gTypeStaticRange :: JSM GType
gTypeStaticRange = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"StaticRange"

-- | Functions for this inteface are in "JSDOM.Storage".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Storage Mozilla Storage documentation>
newtype Storage = Storage { Storage -> JSVal
unStorage :: JSVal }

instance PToJSVal Storage where
  pToJSVal :: Storage -> JSVal
pToJSVal = Storage -> JSVal
unStorage
  {-# INLINE pToJSVal #-}

instance PFromJSVal Storage where
  pFromJSVal :: JSVal -> Storage
pFromJSVal = JSVal -> Storage
Storage
  {-# INLINE pFromJSVal #-}

instance ToJSVal Storage where
  toJSVal :: Storage -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Storage -> JSVal) -> Storage -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Storage -> JSVal
unStorage
  {-# INLINE toJSVal #-}

instance FromJSVal Storage where
  fromJSVal :: JSVal -> JSM (Maybe Storage)
fromJSVal JSVal
v = (JSVal -> Storage) -> Maybe JSVal -> Maybe Storage
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Storage
Storage (Maybe JSVal -> Maybe Storage)
-> JSM (Maybe JSVal) -> JSM (Maybe Storage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Storage
fromJSValUnchecked = Storage -> JSM Storage
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Storage -> JSM Storage)
-> (JSVal -> Storage) -> JSVal -> JSM Storage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Storage
Storage
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Storage where
  makeObject :: Storage -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (Storage -> JSVal) -> Storage -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Storage -> JSVal
unStorage

instance IsGObject Storage where
  typeGType :: Storage -> JSM GType
typeGType Storage
_ = JSM GType
gTypeStorage
  {-# INLINE typeGType #-}

noStorage :: Maybe Storage
noStorage :: Maybe Storage
noStorage = Maybe Storage
forall a. Maybe a
Nothing
{-# INLINE noStorage #-}

gTypeStorage :: JSM GType
gTypeStorage :: JSM GType
gTypeStorage = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Storage"

-- | Functions for this inteface are in "JSDOM.StorageEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/StorageEvent Mozilla StorageEvent documentation>
newtype StorageEvent = StorageEvent { StorageEvent -> JSVal
unStorageEvent :: JSVal }

instance PToJSVal StorageEvent where
  pToJSVal :: StorageEvent -> JSVal
pToJSVal = StorageEvent -> JSVal
unStorageEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal StorageEvent where
  pFromJSVal :: JSVal -> StorageEvent
pFromJSVal = JSVal -> StorageEvent
StorageEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal StorageEvent where
  toJSVal :: StorageEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (StorageEvent -> JSVal) -> StorageEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StorageEvent -> JSVal
unStorageEvent
  {-# INLINE toJSVal #-}

instance FromJSVal StorageEvent where
  fromJSVal :: JSVal -> JSM (Maybe StorageEvent)
fromJSVal JSVal
v = (JSVal -> StorageEvent) -> Maybe JSVal -> Maybe StorageEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> StorageEvent
StorageEvent (Maybe JSVal -> Maybe StorageEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe StorageEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM StorageEvent
fromJSValUnchecked = StorageEvent -> JSM StorageEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (StorageEvent -> JSM StorageEvent)
-> (JSVal -> StorageEvent) -> JSVal -> JSM StorageEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> StorageEvent
StorageEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject StorageEvent where
  makeObject :: StorageEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (StorageEvent -> JSVal) -> StorageEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StorageEvent -> JSVal
unStorageEvent

instance IsEvent StorageEvent
instance IsGObject StorageEvent where
  typeGType :: StorageEvent -> JSM GType
typeGType StorageEvent
_ = JSM GType
gTypeStorageEvent
  {-# INLINE typeGType #-}

noStorageEvent :: Maybe StorageEvent
noStorageEvent :: Maybe StorageEvent
noStorageEvent = Maybe StorageEvent
forall a. Maybe a
Nothing
{-# INLINE noStorageEvent #-}

gTypeStorageEvent :: JSM GType
gTypeStorageEvent :: JSM GType
gTypeStorageEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"StorageEvent"

-- | Functions for this inteface are in "JSDOM.StorageEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/StorageEventInit Mozilla StorageEventInit documentation>
newtype StorageEventInit = StorageEventInit { StorageEventInit -> JSVal
unStorageEventInit :: JSVal }

instance PToJSVal StorageEventInit where
  pToJSVal :: StorageEventInit -> JSVal
pToJSVal = StorageEventInit -> JSVal
unStorageEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal StorageEventInit where
  pFromJSVal :: JSVal -> StorageEventInit
pFromJSVal = JSVal -> StorageEventInit
StorageEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal StorageEventInit where
  toJSVal :: StorageEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (StorageEventInit -> JSVal) -> StorageEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StorageEventInit -> JSVal
unStorageEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal StorageEventInit where
  fromJSVal :: JSVal -> JSM (Maybe StorageEventInit)
fromJSVal JSVal
v = (JSVal -> StorageEventInit)
-> Maybe JSVal -> Maybe StorageEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> StorageEventInit
StorageEventInit (Maybe JSVal -> Maybe StorageEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe StorageEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM StorageEventInit
fromJSValUnchecked = StorageEventInit -> JSM StorageEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (StorageEventInit -> JSM StorageEventInit)
-> (JSVal -> StorageEventInit) -> JSVal -> JSM StorageEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> StorageEventInit
StorageEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject StorageEventInit where
  makeObject :: StorageEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (StorageEventInit -> JSVal) -> StorageEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StorageEventInit -> JSVal
unStorageEventInit

instance IsEventInit StorageEventInit
instance IsGObject StorageEventInit where
  typeGType :: StorageEventInit -> JSM GType
typeGType StorageEventInit
_ = JSM GType
gTypeStorageEventInit
  {-# INLINE typeGType #-}

noStorageEventInit :: Maybe StorageEventInit
noStorageEventInit :: Maybe StorageEventInit
noStorageEventInit = Maybe StorageEventInit
forall a. Maybe a
Nothing
{-# INLINE noStorageEventInit #-}

gTypeStorageEventInit :: JSM GType
gTypeStorageEventInit :: JSM GType
gTypeStorageEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"StorageEventInit"

-- | Functions for this inteface are in "JSDOM.StorageInfo".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/StorageInfo Mozilla StorageInfo documentation>
newtype StorageInfo = StorageInfo { StorageInfo -> JSVal
unStorageInfo :: JSVal }

instance PToJSVal StorageInfo where
  pToJSVal :: StorageInfo -> JSVal
pToJSVal = StorageInfo -> JSVal
unStorageInfo
  {-# INLINE pToJSVal #-}

instance PFromJSVal StorageInfo where
  pFromJSVal :: JSVal -> StorageInfo
pFromJSVal = JSVal -> StorageInfo
StorageInfo
  {-# INLINE pFromJSVal #-}

instance ToJSVal StorageInfo where
  toJSVal :: StorageInfo -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (StorageInfo -> JSVal) -> StorageInfo -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StorageInfo -> JSVal
unStorageInfo
  {-# INLINE toJSVal #-}

instance FromJSVal StorageInfo where
  fromJSVal :: JSVal -> JSM (Maybe StorageInfo)
fromJSVal JSVal
v = (JSVal -> StorageInfo) -> Maybe JSVal -> Maybe StorageInfo
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> StorageInfo
StorageInfo (Maybe JSVal -> Maybe StorageInfo)
-> JSM (Maybe JSVal) -> JSM (Maybe StorageInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM StorageInfo
fromJSValUnchecked = StorageInfo -> JSM StorageInfo
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (StorageInfo -> JSM StorageInfo)
-> (JSVal -> StorageInfo) -> JSVal -> JSM StorageInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> StorageInfo
StorageInfo
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject StorageInfo where
  makeObject :: StorageInfo -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (StorageInfo -> JSVal) -> StorageInfo -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StorageInfo -> JSVal
unStorageInfo

instance IsGObject StorageInfo where
  typeGType :: StorageInfo -> JSM GType
typeGType StorageInfo
_ = JSM GType
gTypeStorageInfo
  {-# INLINE typeGType #-}

noStorageInfo :: Maybe StorageInfo
noStorageInfo :: Maybe StorageInfo
noStorageInfo = Maybe StorageInfo
forall a. Maybe a
Nothing
{-# INLINE noStorageInfo #-}

gTypeStorageInfo :: JSM GType
gTypeStorageInfo :: JSM GType
gTypeStorageInfo = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"StorageInfo"

-- | Functions for this inteface are in "JSDOM.StorageQuota".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/StorageQuota Mozilla StorageQuota documentation>
newtype StorageQuota = StorageQuota { StorageQuota -> JSVal
unStorageQuota :: JSVal }

instance PToJSVal StorageQuota where
  pToJSVal :: StorageQuota -> JSVal
pToJSVal = StorageQuota -> JSVal
unStorageQuota
  {-# INLINE pToJSVal #-}

instance PFromJSVal StorageQuota where
  pFromJSVal :: JSVal -> StorageQuota
pFromJSVal = JSVal -> StorageQuota
StorageQuota
  {-# INLINE pFromJSVal #-}

instance ToJSVal StorageQuota where
  toJSVal :: StorageQuota -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (StorageQuota -> JSVal) -> StorageQuota -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StorageQuota -> JSVal
unStorageQuota
  {-# INLINE toJSVal #-}

instance FromJSVal StorageQuota where
  fromJSVal :: JSVal -> JSM (Maybe StorageQuota)
fromJSVal JSVal
v = (JSVal -> StorageQuota) -> Maybe JSVal -> Maybe StorageQuota
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> StorageQuota
StorageQuota (Maybe JSVal -> Maybe StorageQuota)
-> JSM (Maybe JSVal) -> JSM (Maybe StorageQuota)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM StorageQuota
fromJSValUnchecked = StorageQuota -> JSM StorageQuota
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (StorageQuota -> JSM StorageQuota)
-> (JSVal -> StorageQuota) -> JSVal -> JSM StorageQuota
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> StorageQuota
StorageQuota
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject StorageQuota where
  makeObject :: StorageQuota -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (StorageQuota -> JSVal) -> StorageQuota -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StorageQuota -> JSVal
unStorageQuota

instance IsGObject StorageQuota where
  typeGType :: StorageQuota -> JSM GType
typeGType StorageQuota
_ = JSM GType
gTypeStorageQuota
  {-# INLINE typeGType #-}

noStorageQuota :: Maybe StorageQuota
noStorageQuota :: Maybe StorageQuota
noStorageQuota = Maybe StorageQuota
forall a. Maybe a
Nothing
{-# INLINE noStorageQuota #-}

gTypeStorageQuota :: JSM GType
gTypeStorageQuota :: JSM GType
gTypeStorageQuota = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"StorageQuota"

-- | Functions for this inteface are in "JSDOM.StyleMedia".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/StyleMedia Mozilla StyleMedia documentation>
newtype StyleMedia = StyleMedia { StyleMedia -> JSVal
unStyleMedia :: JSVal }

instance PToJSVal StyleMedia where
  pToJSVal :: StyleMedia -> JSVal
pToJSVal = StyleMedia -> JSVal
unStyleMedia
  {-# INLINE pToJSVal #-}

instance PFromJSVal StyleMedia where
  pFromJSVal :: JSVal -> StyleMedia
pFromJSVal = JSVal -> StyleMedia
StyleMedia
  {-# INLINE pFromJSVal #-}

instance ToJSVal StyleMedia where
  toJSVal :: StyleMedia -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (StyleMedia -> JSVal) -> StyleMedia -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StyleMedia -> JSVal
unStyleMedia
  {-# INLINE toJSVal #-}

instance FromJSVal StyleMedia where
  fromJSVal :: JSVal -> JSM (Maybe StyleMedia)
fromJSVal JSVal
v = (JSVal -> StyleMedia) -> Maybe JSVal -> Maybe StyleMedia
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> StyleMedia
StyleMedia (Maybe JSVal -> Maybe StyleMedia)
-> JSM (Maybe JSVal) -> JSM (Maybe StyleMedia)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM StyleMedia
fromJSValUnchecked = StyleMedia -> JSM StyleMedia
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (StyleMedia -> JSM StyleMedia)
-> (JSVal -> StyleMedia) -> JSVal -> JSM StyleMedia
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> StyleMedia
StyleMedia
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject StyleMedia where
  makeObject :: StyleMedia -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (StyleMedia -> JSVal) -> StyleMedia -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StyleMedia -> JSVal
unStyleMedia

instance IsGObject StyleMedia where
  typeGType :: StyleMedia -> JSM GType
typeGType StyleMedia
_ = JSM GType
gTypeStyleMedia
  {-# INLINE typeGType #-}

noStyleMedia :: Maybe StyleMedia
noStyleMedia :: Maybe StyleMedia
noStyleMedia = Maybe StyleMedia
forall a. Maybe a
Nothing
{-# INLINE noStyleMedia #-}

gTypeStyleMedia :: JSM GType
gTypeStyleMedia :: JSM GType
gTypeStyleMedia = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"StyleMedia"

-- | Functions for this inteface are in "JSDOM.StyleSheet".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/StyleSheet Mozilla StyleSheet documentation>
newtype StyleSheet = StyleSheet { StyleSheet -> JSVal
unStyleSheet :: JSVal }

instance PToJSVal StyleSheet where
  pToJSVal :: StyleSheet -> JSVal
pToJSVal = StyleSheet -> JSVal
unStyleSheet
  {-# INLINE pToJSVal #-}

instance PFromJSVal StyleSheet where
  pFromJSVal :: JSVal -> StyleSheet
pFromJSVal = JSVal -> StyleSheet
StyleSheet
  {-# INLINE pFromJSVal #-}

instance ToJSVal StyleSheet where
  toJSVal :: StyleSheet -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (StyleSheet -> JSVal) -> StyleSheet -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StyleSheet -> JSVal
unStyleSheet
  {-# INLINE toJSVal #-}

instance FromJSVal StyleSheet where
  fromJSVal :: JSVal -> JSM (Maybe StyleSheet)
fromJSVal JSVal
v = (JSVal -> StyleSheet) -> Maybe JSVal -> Maybe StyleSheet
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> StyleSheet
StyleSheet (Maybe JSVal -> Maybe StyleSheet)
-> JSM (Maybe JSVal) -> JSM (Maybe StyleSheet)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM StyleSheet
fromJSValUnchecked = StyleSheet -> JSM StyleSheet
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (StyleSheet -> JSM StyleSheet)
-> (JSVal -> StyleSheet) -> JSVal -> JSM StyleSheet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> StyleSheet
StyleSheet
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject StyleSheet where
  makeObject :: StyleSheet -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (StyleSheet -> JSVal) -> StyleSheet -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StyleSheet -> JSVal
unStyleSheet

class (IsGObject o) => IsStyleSheet o
toStyleSheet :: IsStyleSheet o => o -> StyleSheet
toStyleSheet :: forall o. IsStyleSheet o => o -> StyleSheet
toStyleSheet = JSVal -> StyleSheet
StyleSheet (JSVal -> StyleSheet) -> (o -> JSVal) -> o -> StyleSheet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsStyleSheet StyleSheet
instance IsGObject StyleSheet where
  typeGType :: StyleSheet -> JSM GType
typeGType StyleSheet
_ = JSM GType
gTypeStyleSheet
  {-# INLINE typeGType #-}

noStyleSheet :: Maybe StyleSheet
noStyleSheet :: Maybe StyleSheet
noStyleSheet = Maybe StyleSheet
forall a. Maybe a
Nothing
{-# INLINE noStyleSheet #-}

gTypeStyleSheet :: JSM GType
gTypeStyleSheet :: JSM GType
gTypeStyleSheet = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"StyleSheet"

-- | Functions for this inteface are in "JSDOM.StyleSheetList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/StyleSheetList Mozilla StyleSheetList documentation>
newtype StyleSheetList = StyleSheetList { StyleSheetList -> JSVal
unStyleSheetList :: JSVal }

instance PToJSVal StyleSheetList where
  pToJSVal :: StyleSheetList -> JSVal
pToJSVal = StyleSheetList -> JSVal
unStyleSheetList
  {-# INLINE pToJSVal #-}

instance PFromJSVal StyleSheetList where
  pFromJSVal :: JSVal -> StyleSheetList
pFromJSVal = JSVal -> StyleSheetList
StyleSheetList
  {-# INLINE pFromJSVal #-}

instance ToJSVal StyleSheetList where
  toJSVal :: StyleSheetList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (StyleSheetList -> JSVal) -> StyleSheetList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StyleSheetList -> JSVal
unStyleSheetList
  {-# INLINE toJSVal #-}

instance FromJSVal StyleSheetList where
  fromJSVal :: JSVal -> JSM (Maybe StyleSheetList)
fromJSVal JSVal
v = (JSVal -> StyleSheetList) -> Maybe JSVal -> Maybe StyleSheetList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> StyleSheetList
StyleSheetList (Maybe JSVal -> Maybe StyleSheetList)
-> JSM (Maybe JSVal) -> JSM (Maybe StyleSheetList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM StyleSheetList
fromJSValUnchecked = StyleSheetList -> JSM StyleSheetList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (StyleSheetList -> JSM StyleSheetList)
-> (JSVal -> StyleSheetList) -> JSVal -> JSM StyleSheetList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> StyleSheetList
StyleSheetList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject StyleSheetList where
  makeObject :: StyleSheetList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (StyleSheetList -> JSVal) -> StyleSheetList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StyleSheetList -> JSVal
unStyleSheetList

instance IsGObject StyleSheetList where
  typeGType :: StyleSheetList -> JSM GType
typeGType StyleSheetList
_ = JSM GType
gTypeStyleSheetList
  {-# INLINE typeGType #-}

noStyleSheetList :: Maybe StyleSheetList
noStyleSheetList :: Maybe StyleSheetList
noStyleSheetList = Maybe StyleSheetList
forall a. Maybe a
Nothing
{-# INLINE noStyleSheetList #-}

gTypeStyleSheetList :: JSM GType
gTypeStyleSheetList :: JSM GType
gTypeStyleSheetList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"StyleSheetList"

-- | Functions for this inteface are in "JSDOM.SubtleCrypto".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitSubtleCrypto Mozilla WebKitSubtleCrypto documentation>
newtype SubtleCrypto = SubtleCrypto { SubtleCrypto -> JSVal
unSubtleCrypto :: JSVal }

instance PToJSVal SubtleCrypto where
  pToJSVal :: SubtleCrypto -> JSVal
pToJSVal = SubtleCrypto -> JSVal
unSubtleCrypto
  {-# INLINE pToJSVal #-}

instance PFromJSVal SubtleCrypto where
  pFromJSVal :: JSVal -> SubtleCrypto
pFromJSVal = JSVal -> SubtleCrypto
SubtleCrypto
  {-# INLINE pFromJSVal #-}

instance ToJSVal SubtleCrypto where
  toJSVal :: SubtleCrypto -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (SubtleCrypto -> JSVal) -> SubtleCrypto -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SubtleCrypto -> JSVal
unSubtleCrypto
  {-# INLINE toJSVal #-}

instance FromJSVal SubtleCrypto where
  fromJSVal :: JSVal -> JSM (Maybe SubtleCrypto)
fromJSVal JSVal
v = (JSVal -> SubtleCrypto) -> Maybe JSVal -> Maybe SubtleCrypto
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> SubtleCrypto
SubtleCrypto (Maybe JSVal -> Maybe SubtleCrypto)
-> JSM (Maybe JSVal) -> JSM (Maybe SubtleCrypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM SubtleCrypto
fromJSValUnchecked = SubtleCrypto -> JSM SubtleCrypto
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (SubtleCrypto -> JSM SubtleCrypto)
-> (JSVal -> SubtleCrypto) -> JSVal -> JSM SubtleCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> SubtleCrypto
SubtleCrypto
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject SubtleCrypto where
  makeObject :: SubtleCrypto -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (SubtleCrypto -> JSVal) -> SubtleCrypto -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SubtleCrypto -> JSVal
unSubtleCrypto

instance IsGObject SubtleCrypto where
  typeGType :: SubtleCrypto -> JSM GType
typeGType SubtleCrypto
_ = JSM GType
gTypeSubtleCrypto
  {-# INLINE typeGType #-}

noSubtleCrypto :: Maybe SubtleCrypto
noSubtleCrypto :: Maybe SubtleCrypto
noSubtleCrypto = Maybe SubtleCrypto
forall a. Maybe a
Nothing
{-# INLINE noSubtleCrypto #-}

gTypeSubtleCrypto :: JSM GType
gTypeSubtleCrypto :: JSM GType
gTypeSubtleCrypto = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitSubtleCrypto"

-- | Functions for this inteface are in "JSDOM.Text".
-- Base interface functions are in:
--
--     * "JSDOM.CharacterData"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.NonDocumentTypeChildNode"
--     * "JSDOM.ChildNode"
--     * "JSDOM.Slotable"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Text Mozilla Text documentation>
newtype Text = Text { Text -> JSVal
unText :: JSVal }

instance PToJSVal Text where
  pToJSVal :: Text -> JSVal
pToJSVal = Text -> JSVal
unText
  {-# INLINE pToJSVal #-}

instance PFromJSVal Text where
  pFromJSVal :: JSVal -> Text
pFromJSVal = JSVal -> Text
Text
  {-# INLINE pFromJSVal #-}

instance ToJSVal Text where
  toJSVal :: Text -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Text -> JSVal) -> Text -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> JSVal
unText
  {-# INLINE toJSVal #-}

instance FromJSVal Text where
  fromJSVal :: JSVal -> JSM (Maybe Text)
fromJSVal JSVal
v = (JSVal -> Text) -> Maybe JSVal -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Text
Text (Maybe JSVal -> Maybe Text)
-> JSM (Maybe JSVal) -> JSM (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Text
fromJSValUnchecked = Text -> JSM Text
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> JSM Text) -> (JSVal -> Text) -> JSVal -> JSM Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Text
Text
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Text where
  makeObject :: Text -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Text -> JSVal) -> Text -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> JSVal
unText

class (IsCharacterData o, IsNode o, IsEventTarget o, IsNonDocumentTypeChildNode o, IsChildNode o, IsSlotable o, IsGObject o) => IsText o
toText :: IsText o => o -> Text
toText :: forall o. IsText o => o -> Text
toText = JSVal -> Text
Text (JSVal -> Text) -> (o -> JSVal) -> o -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
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 :: Text -> JSM GType
typeGType Text
_ = JSM GType
gTypeText
  {-# INLINE typeGType #-}

noText :: Maybe Text
noText :: Maybe Text
noText = Maybe Text
forall a. Maybe a
Nothing
{-# INLINE noText #-}

gTypeText :: JSM GType
gTypeText :: JSM GType
gTypeText = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Text"

-- | Functions for this inteface are in "JSDOM.TextDecodeOptions".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TextDecodeOptions Mozilla TextDecodeOptions documentation>
newtype TextDecodeOptions = TextDecodeOptions { TextDecodeOptions -> JSVal
unTextDecodeOptions :: JSVal }

instance PToJSVal TextDecodeOptions where
  pToJSVal :: TextDecodeOptions -> JSVal
pToJSVal = TextDecodeOptions -> JSVal
unTextDecodeOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal TextDecodeOptions where
  pFromJSVal :: JSVal -> TextDecodeOptions
pFromJSVal = JSVal -> TextDecodeOptions
TextDecodeOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal TextDecodeOptions where
  toJSVal :: TextDecodeOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TextDecodeOptions -> JSVal) -> TextDecodeOptions -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDecodeOptions -> JSVal
unTextDecodeOptions
  {-# INLINE toJSVal #-}

instance FromJSVal TextDecodeOptions where
  fromJSVal :: JSVal -> JSM (Maybe TextDecodeOptions)
fromJSVal JSVal
v = (JSVal -> TextDecodeOptions)
-> Maybe JSVal -> Maybe TextDecodeOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TextDecodeOptions
TextDecodeOptions (Maybe JSVal -> Maybe TextDecodeOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe TextDecodeOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TextDecodeOptions
fromJSValUnchecked = TextDecodeOptions -> JSM TextDecodeOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TextDecodeOptions -> JSM TextDecodeOptions)
-> (JSVal -> TextDecodeOptions) -> JSVal -> JSM TextDecodeOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TextDecodeOptions
TextDecodeOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TextDecodeOptions where
  makeObject :: TextDecodeOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TextDecodeOptions -> JSVal) -> TextDecodeOptions -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDecodeOptions -> JSVal
unTextDecodeOptions

instance IsGObject TextDecodeOptions where
  typeGType :: TextDecodeOptions -> JSM GType
typeGType TextDecodeOptions
_ = JSM GType
gTypeTextDecodeOptions
  {-# INLINE typeGType #-}

noTextDecodeOptions :: Maybe TextDecodeOptions
noTextDecodeOptions :: Maybe TextDecodeOptions
noTextDecodeOptions = Maybe TextDecodeOptions
forall a. Maybe a
Nothing
{-# INLINE noTextDecodeOptions #-}

gTypeTextDecodeOptions :: JSM GType
gTypeTextDecodeOptions :: JSM GType
gTypeTextDecodeOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TextDecodeOptions"

-- | Functions for this inteface are in "JSDOM.TextDecoder".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TextDecoder Mozilla TextDecoder documentation>
newtype TextDecoder = TextDecoder { TextDecoder -> JSVal
unTextDecoder :: JSVal }

instance PToJSVal TextDecoder where
  pToJSVal :: TextDecoder -> JSVal
pToJSVal = TextDecoder -> JSVal
unTextDecoder
  {-# INLINE pToJSVal #-}

instance PFromJSVal TextDecoder where
  pFromJSVal :: JSVal -> TextDecoder
pFromJSVal = JSVal -> TextDecoder
TextDecoder
  {-# INLINE pFromJSVal #-}

instance ToJSVal TextDecoder where
  toJSVal :: TextDecoder -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TextDecoder -> JSVal) -> TextDecoder -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDecoder -> JSVal
unTextDecoder
  {-# INLINE toJSVal #-}

instance FromJSVal TextDecoder where
  fromJSVal :: JSVal -> JSM (Maybe TextDecoder)
fromJSVal JSVal
v = (JSVal -> TextDecoder) -> Maybe JSVal -> Maybe TextDecoder
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TextDecoder
TextDecoder (Maybe JSVal -> Maybe TextDecoder)
-> JSM (Maybe JSVal) -> JSM (Maybe TextDecoder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TextDecoder
fromJSValUnchecked = TextDecoder -> JSM TextDecoder
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TextDecoder -> JSM TextDecoder)
-> (JSVal -> TextDecoder) -> JSVal -> JSM TextDecoder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TextDecoder
TextDecoder
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TextDecoder where
  makeObject :: TextDecoder -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TextDecoder -> JSVal) -> TextDecoder -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDecoder -> JSVal
unTextDecoder

instance IsGObject TextDecoder where
  typeGType :: TextDecoder -> JSM GType
typeGType TextDecoder
_ = JSM GType
gTypeTextDecoder
  {-# INLINE typeGType #-}

noTextDecoder :: Maybe TextDecoder
noTextDecoder :: Maybe TextDecoder
noTextDecoder = Maybe TextDecoder
forall a. Maybe a
Nothing
{-# INLINE noTextDecoder #-}

gTypeTextDecoder :: JSM GType
gTypeTextDecoder :: JSM GType
gTypeTextDecoder = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TextDecoder"

-- | Functions for this inteface are in "JSDOM.TextDecoderOptions".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TextDecoderOptions Mozilla TextDecoderOptions documentation>
newtype TextDecoderOptions = TextDecoderOptions { TextDecoderOptions -> JSVal
unTextDecoderOptions :: JSVal }

instance PToJSVal TextDecoderOptions where
  pToJSVal :: TextDecoderOptions -> JSVal
pToJSVal = TextDecoderOptions -> JSVal
unTextDecoderOptions
  {-# INLINE pToJSVal #-}

instance PFromJSVal TextDecoderOptions where
  pFromJSVal :: JSVal -> TextDecoderOptions
pFromJSVal = JSVal -> TextDecoderOptions
TextDecoderOptions
  {-# INLINE pFromJSVal #-}

instance ToJSVal TextDecoderOptions where
  toJSVal :: TextDecoderOptions -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TextDecoderOptions -> JSVal) -> TextDecoderOptions -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDecoderOptions -> JSVal
unTextDecoderOptions
  {-# INLINE toJSVal #-}

instance FromJSVal TextDecoderOptions where
  fromJSVal :: JSVal -> JSM (Maybe TextDecoderOptions)
fromJSVal JSVal
v = (JSVal -> TextDecoderOptions)
-> Maybe JSVal -> Maybe TextDecoderOptions
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TextDecoderOptions
TextDecoderOptions (Maybe JSVal -> Maybe TextDecoderOptions)
-> JSM (Maybe JSVal) -> JSM (Maybe TextDecoderOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TextDecoderOptions
fromJSValUnchecked = TextDecoderOptions -> JSM TextDecoderOptions
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TextDecoderOptions -> JSM TextDecoderOptions)
-> (JSVal -> TextDecoderOptions) -> JSVal -> JSM TextDecoderOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TextDecoderOptions
TextDecoderOptions
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TextDecoderOptions where
  makeObject :: TextDecoderOptions -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TextDecoderOptions -> JSVal)
-> TextDecoderOptions
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDecoderOptions -> JSVal
unTextDecoderOptions

instance IsGObject TextDecoderOptions where
  typeGType :: TextDecoderOptions -> JSM GType
typeGType TextDecoderOptions
_ = JSM GType
gTypeTextDecoderOptions
  {-# INLINE typeGType #-}

noTextDecoderOptions :: Maybe TextDecoderOptions
noTextDecoderOptions :: Maybe TextDecoderOptions
noTextDecoderOptions = Maybe TextDecoderOptions
forall a. Maybe a
Nothing
{-# INLINE noTextDecoderOptions #-}

gTypeTextDecoderOptions :: JSM GType
gTypeTextDecoderOptions :: JSM GType
gTypeTextDecoderOptions = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TextDecoderOptions"

-- | Functions for this inteface are in "JSDOM.TextEncoder".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TextEncoder Mozilla TextEncoder documentation>
newtype TextEncoder = TextEncoder { TextEncoder -> JSVal
unTextEncoder :: JSVal }

instance PToJSVal TextEncoder where
  pToJSVal :: TextEncoder -> JSVal
pToJSVal = TextEncoder -> JSVal
unTextEncoder
  {-# INLINE pToJSVal #-}

instance PFromJSVal TextEncoder where
  pFromJSVal :: JSVal -> TextEncoder
pFromJSVal = JSVal -> TextEncoder
TextEncoder
  {-# INLINE pFromJSVal #-}

instance ToJSVal TextEncoder where
  toJSVal :: TextEncoder -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TextEncoder -> JSVal) -> TextEncoder -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextEncoder -> JSVal
unTextEncoder
  {-# INLINE toJSVal #-}

instance FromJSVal TextEncoder where
  fromJSVal :: JSVal -> JSM (Maybe TextEncoder)
fromJSVal JSVal
v = (JSVal -> TextEncoder) -> Maybe JSVal -> Maybe TextEncoder
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TextEncoder
TextEncoder (Maybe JSVal -> Maybe TextEncoder)
-> JSM (Maybe JSVal) -> JSM (Maybe TextEncoder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TextEncoder
fromJSValUnchecked = TextEncoder -> JSM TextEncoder
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TextEncoder -> JSM TextEncoder)
-> (JSVal -> TextEncoder) -> JSVal -> JSM TextEncoder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TextEncoder
TextEncoder
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TextEncoder where
  makeObject :: TextEncoder -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TextEncoder -> JSVal) -> TextEncoder -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextEncoder -> JSVal
unTextEncoder

instance IsGObject TextEncoder where
  typeGType :: TextEncoder -> JSM GType
typeGType TextEncoder
_ = JSM GType
gTypeTextEncoder
  {-# INLINE typeGType #-}

noTextEncoder :: Maybe TextEncoder
noTextEncoder :: Maybe TextEncoder
noTextEncoder = Maybe TextEncoder
forall a. Maybe a
Nothing
{-# INLINE noTextEncoder #-}

gTypeTextEncoder :: JSM GType
gTypeTextEncoder :: JSM GType
gTypeTextEncoder = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TextEncoder"

-- | Functions for this inteface are in "JSDOM.TextEvent".
-- Base interface functions are in:
--
--     * "JSDOM.UIEvent"
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TextEvent Mozilla TextEvent documentation>
newtype TextEvent = TextEvent { TextEvent -> JSVal
unTextEvent :: JSVal }

instance PToJSVal TextEvent where
  pToJSVal :: TextEvent -> JSVal
pToJSVal = TextEvent -> JSVal
unTextEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal TextEvent where
  pFromJSVal :: JSVal -> TextEvent
pFromJSVal = JSVal -> TextEvent
TextEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal TextEvent where
  toJSVal :: TextEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TextEvent -> JSVal) -> TextEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextEvent -> JSVal
unTextEvent
  {-# INLINE toJSVal #-}

instance FromJSVal TextEvent where
  fromJSVal :: JSVal -> JSM (Maybe TextEvent)
fromJSVal JSVal
v = (JSVal -> TextEvent) -> Maybe JSVal -> Maybe TextEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TextEvent
TextEvent (Maybe JSVal -> Maybe TextEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe TextEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TextEvent
fromJSValUnchecked = TextEvent -> JSM TextEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TextEvent -> JSM TextEvent)
-> (JSVal -> TextEvent) -> JSVal -> JSM TextEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TextEvent
TextEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TextEvent where
  makeObject :: TextEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TextEvent -> JSVal) -> TextEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextEvent -> JSVal
unTextEvent

instance IsUIEvent TextEvent
instance IsEvent TextEvent
instance IsGObject TextEvent where
  typeGType :: TextEvent -> JSM GType
typeGType TextEvent
_ = JSM GType
gTypeTextEvent
  {-# INLINE typeGType #-}

noTextEvent :: Maybe TextEvent
noTextEvent :: Maybe TextEvent
noTextEvent = Maybe TextEvent
forall a. Maybe a
Nothing
{-# INLINE noTextEvent #-}

gTypeTextEvent :: JSM GType
gTypeTextEvent :: JSM GType
gTypeTextEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TextEvent"

-- | Functions for this inteface are in "JSDOM.TextMetrics".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TextMetrics Mozilla TextMetrics documentation>
newtype TextMetrics = TextMetrics { TextMetrics -> JSVal
unTextMetrics :: JSVal }

instance PToJSVal TextMetrics where
  pToJSVal :: TextMetrics -> JSVal
pToJSVal = TextMetrics -> JSVal
unTextMetrics
  {-# INLINE pToJSVal #-}

instance PFromJSVal TextMetrics where
  pFromJSVal :: JSVal -> TextMetrics
pFromJSVal = JSVal -> TextMetrics
TextMetrics
  {-# INLINE pFromJSVal #-}

instance ToJSVal TextMetrics where
  toJSVal :: TextMetrics -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TextMetrics -> JSVal) -> TextMetrics -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextMetrics -> JSVal
unTextMetrics
  {-# INLINE toJSVal #-}

instance FromJSVal TextMetrics where
  fromJSVal :: JSVal -> JSM (Maybe TextMetrics)
fromJSVal JSVal
v = (JSVal -> TextMetrics) -> Maybe JSVal -> Maybe TextMetrics
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TextMetrics
TextMetrics (Maybe JSVal -> Maybe TextMetrics)
-> JSM (Maybe JSVal) -> JSM (Maybe TextMetrics)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TextMetrics
fromJSValUnchecked = TextMetrics -> JSM TextMetrics
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TextMetrics -> JSM TextMetrics)
-> (JSVal -> TextMetrics) -> JSVal -> JSM TextMetrics
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TextMetrics
TextMetrics
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TextMetrics where
  makeObject :: TextMetrics -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TextMetrics -> JSVal) -> TextMetrics -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextMetrics -> JSVal
unTextMetrics

instance IsGObject TextMetrics where
  typeGType :: TextMetrics -> JSM GType
typeGType TextMetrics
_ = JSM GType
gTypeTextMetrics
  {-# INLINE typeGType #-}

noTextMetrics :: Maybe TextMetrics
noTextMetrics :: Maybe TextMetrics
noTextMetrics = Maybe TextMetrics
forall a. Maybe a
Nothing
{-# INLINE noTextMetrics #-}

gTypeTextMetrics :: JSM GType
gTypeTextMetrics :: JSM GType
gTypeTextMetrics = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TextMetrics"

-- | Functions for this inteface are in "JSDOM.TextTrack".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TextTrack Mozilla TextTrack documentation>
newtype TextTrack = TextTrack { TextTrack -> JSVal
unTextTrack :: JSVal }

instance PToJSVal TextTrack where
  pToJSVal :: TextTrack -> JSVal
pToJSVal = TextTrack -> JSVal
unTextTrack
  {-# INLINE pToJSVal #-}

instance PFromJSVal TextTrack where
  pFromJSVal :: JSVal -> TextTrack
pFromJSVal = JSVal -> TextTrack
TextTrack
  {-# INLINE pFromJSVal #-}

instance ToJSVal TextTrack where
  toJSVal :: TextTrack -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TextTrack -> JSVal) -> TextTrack -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextTrack -> JSVal
unTextTrack
  {-# INLINE toJSVal #-}

instance FromJSVal TextTrack where
  fromJSVal :: JSVal -> JSM (Maybe TextTrack)
fromJSVal JSVal
v = (JSVal -> TextTrack) -> Maybe JSVal -> Maybe TextTrack
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TextTrack
TextTrack (Maybe JSVal -> Maybe TextTrack)
-> JSM (Maybe JSVal) -> JSM (Maybe TextTrack)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TextTrack
fromJSValUnchecked = TextTrack -> JSM TextTrack
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TextTrack -> JSM TextTrack)
-> (JSVal -> TextTrack) -> JSVal -> JSM TextTrack
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TextTrack
TextTrack
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TextTrack where
  makeObject :: TextTrack -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TextTrack -> JSVal) -> TextTrack -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextTrack -> JSVal
unTextTrack

instance IsEventTarget TextTrack
instance IsGObject TextTrack where
  typeGType :: TextTrack -> JSM GType
typeGType TextTrack
_ = JSM GType
gTypeTextTrack
  {-# INLINE typeGType #-}

noTextTrack :: Maybe TextTrack
noTextTrack :: Maybe TextTrack
noTextTrack = Maybe TextTrack
forall a. Maybe a
Nothing
{-# INLINE noTextTrack #-}

gTypeTextTrack :: JSM GType
gTypeTextTrack :: JSM GType
gTypeTextTrack = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TextTrack"

-- | Functions for this inteface are in "JSDOM.TextTrackCue".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TextTrackCue Mozilla TextTrackCue documentation>
newtype TextTrackCue = TextTrackCue { TextTrackCue -> JSVal
unTextTrackCue :: JSVal }

instance PToJSVal TextTrackCue where
  pToJSVal :: TextTrackCue -> JSVal
pToJSVal = TextTrackCue -> JSVal
unTextTrackCue
  {-# INLINE pToJSVal #-}

instance PFromJSVal TextTrackCue where
  pFromJSVal :: JSVal -> TextTrackCue
pFromJSVal = JSVal -> TextTrackCue
TextTrackCue
  {-# INLINE pFromJSVal #-}

instance ToJSVal TextTrackCue where
  toJSVal :: TextTrackCue -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TextTrackCue -> JSVal) -> TextTrackCue -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextTrackCue -> JSVal
unTextTrackCue
  {-# INLINE toJSVal #-}

instance FromJSVal TextTrackCue where
  fromJSVal :: JSVal -> JSM (Maybe TextTrackCue)
fromJSVal JSVal
v = (JSVal -> TextTrackCue) -> Maybe JSVal -> Maybe TextTrackCue
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TextTrackCue
TextTrackCue (Maybe JSVal -> Maybe TextTrackCue)
-> JSM (Maybe JSVal) -> JSM (Maybe TextTrackCue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TextTrackCue
fromJSValUnchecked = TextTrackCue -> JSM TextTrackCue
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TextTrackCue -> JSM TextTrackCue)
-> (JSVal -> TextTrackCue) -> JSVal -> JSM TextTrackCue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TextTrackCue
TextTrackCue
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TextTrackCue where
  makeObject :: TextTrackCue -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TextTrackCue -> JSVal) -> TextTrackCue -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextTrackCue -> JSVal
unTextTrackCue

class (IsEventTarget o, IsGObject o) => IsTextTrackCue o
toTextTrackCue :: IsTextTrackCue o => o -> TextTrackCue
toTextTrackCue :: forall o. IsTextTrackCue o => o -> TextTrackCue
toTextTrackCue = JSVal -> TextTrackCue
TextTrackCue (JSVal -> TextTrackCue) -> (o -> JSVal) -> o -> TextTrackCue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsTextTrackCue TextTrackCue
instance IsEventTarget TextTrackCue
instance IsGObject TextTrackCue where
  typeGType :: TextTrackCue -> JSM GType
typeGType TextTrackCue
_ = JSM GType
gTypeTextTrackCue
  {-# INLINE typeGType #-}

noTextTrackCue :: Maybe TextTrackCue
noTextTrackCue :: Maybe TextTrackCue
noTextTrackCue = Maybe TextTrackCue
forall a. Maybe a
Nothing
{-# INLINE noTextTrackCue #-}

gTypeTextTrackCue :: JSM GType
gTypeTextTrackCue :: JSM GType
gTypeTextTrackCue = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TextTrackCue"

-- | Functions for this inteface are in "JSDOM.TextTrackCueList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TextTrackCueList Mozilla TextTrackCueList documentation>
newtype TextTrackCueList = TextTrackCueList { TextTrackCueList -> JSVal
unTextTrackCueList :: JSVal }

instance PToJSVal TextTrackCueList where
  pToJSVal :: TextTrackCueList -> JSVal
pToJSVal = TextTrackCueList -> JSVal
unTextTrackCueList
  {-# INLINE pToJSVal #-}

instance PFromJSVal TextTrackCueList where
  pFromJSVal :: JSVal -> TextTrackCueList
pFromJSVal = JSVal -> TextTrackCueList
TextTrackCueList
  {-# INLINE pFromJSVal #-}

instance ToJSVal TextTrackCueList where
  toJSVal :: TextTrackCueList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TextTrackCueList -> JSVal) -> TextTrackCueList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextTrackCueList -> JSVal
unTextTrackCueList
  {-# INLINE toJSVal #-}

instance FromJSVal TextTrackCueList where
  fromJSVal :: JSVal -> JSM (Maybe TextTrackCueList)
fromJSVal JSVal
v = (JSVal -> TextTrackCueList)
-> Maybe JSVal -> Maybe TextTrackCueList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TextTrackCueList
TextTrackCueList (Maybe JSVal -> Maybe TextTrackCueList)
-> JSM (Maybe JSVal) -> JSM (Maybe TextTrackCueList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TextTrackCueList
fromJSValUnchecked = TextTrackCueList -> JSM TextTrackCueList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TextTrackCueList -> JSM TextTrackCueList)
-> (JSVal -> TextTrackCueList) -> JSVal -> JSM TextTrackCueList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TextTrackCueList
TextTrackCueList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TextTrackCueList where
  makeObject :: TextTrackCueList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TextTrackCueList -> JSVal) -> TextTrackCueList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextTrackCueList -> JSVal
unTextTrackCueList

instance IsGObject TextTrackCueList where
  typeGType :: TextTrackCueList -> JSM GType
typeGType TextTrackCueList
_ = JSM GType
gTypeTextTrackCueList
  {-# INLINE typeGType #-}

noTextTrackCueList :: Maybe TextTrackCueList
noTextTrackCueList :: Maybe TextTrackCueList
noTextTrackCueList = Maybe TextTrackCueList
forall a. Maybe a
Nothing
{-# INLINE noTextTrackCueList #-}

gTypeTextTrackCueList :: JSM GType
gTypeTextTrackCueList :: JSM GType
gTypeTextTrackCueList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TextTrackCueList"

-- | Functions for this inteface are in "JSDOM.TextTrackList".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TextTrackList Mozilla TextTrackList documentation>
newtype TextTrackList = TextTrackList { TextTrackList -> JSVal
unTextTrackList :: JSVal }

instance PToJSVal TextTrackList where
  pToJSVal :: TextTrackList -> JSVal
pToJSVal = TextTrackList -> JSVal
unTextTrackList
  {-# INLINE pToJSVal #-}

instance PFromJSVal TextTrackList where
  pFromJSVal :: JSVal -> TextTrackList
pFromJSVal = JSVal -> TextTrackList
TextTrackList
  {-# INLINE pFromJSVal #-}

instance ToJSVal TextTrackList where
  toJSVal :: TextTrackList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TextTrackList -> JSVal) -> TextTrackList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextTrackList -> JSVal
unTextTrackList
  {-# INLINE toJSVal #-}

instance FromJSVal TextTrackList where
  fromJSVal :: JSVal -> JSM (Maybe TextTrackList)
fromJSVal JSVal
v = (JSVal -> TextTrackList) -> Maybe JSVal -> Maybe TextTrackList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TextTrackList
TextTrackList (Maybe JSVal -> Maybe TextTrackList)
-> JSM (Maybe JSVal) -> JSM (Maybe TextTrackList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TextTrackList
fromJSValUnchecked = TextTrackList -> JSM TextTrackList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TextTrackList -> JSM TextTrackList)
-> (JSVal -> TextTrackList) -> JSVal -> JSM TextTrackList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TextTrackList
TextTrackList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TextTrackList where
  makeObject :: TextTrackList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TextTrackList -> JSVal) -> TextTrackList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextTrackList -> JSVal
unTextTrackList

instance IsEventTarget TextTrackList
instance IsGObject TextTrackList where
  typeGType :: TextTrackList -> JSM GType
typeGType TextTrackList
_ = JSM GType
gTypeTextTrackList
  {-# INLINE typeGType #-}

noTextTrackList :: Maybe TextTrackList
noTextTrackList :: Maybe TextTrackList
noTextTrackList = Maybe TextTrackList
forall a. Maybe a
Nothing
{-# INLINE noTextTrackList #-}

gTypeTextTrackList :: JSM GType
gTypeTextTrackList :: JSM GType
gTypeTextTrackList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TextTrackList"

-- | Functions for this inteface are in "JSDOM.TimeRanges".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TimeRanges Mozilla TimeRanges documentation>
newtype TimeRanges = TimeRanges { TimeRanges -> JSVal
unTimeRanges :: JSVal }

instance PToJSVal TimeRanges where
  pToJSVal :: TimeRanges -> JSVal
pToJSVal = TimeRanges -> JSVal
unTimeRanges
  {-# INLINE pToJSVal #-}

instance PFromJSVal TimeRanges where
  pFromJSVal :: JSVal -> TimeRanges
pFromJSVal = JSVal -> TimeRanges
TimeRanges
  {-# INLINE pFromJSVal #-}

instance ToJSVal TimeRanges where
  toJSVal :: TimeRanges -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TimeRanges -> JSVal) -> TimeRanges -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeRanges -> JSVal
unTimeRanges
  {-# INLINE toJSVal #-}

instance FromJSVal TimeRanges where
  fromJSVal :: JSVal -> JSM (Maybe TimeRanges)
fromJSVal JSVal
v = (JSVal -> TimeRanges) -> Maybe JSVal -> Maybe TimeRanges
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TimeRanges
TimeRanges (Maybe JSVal -> Maybe TimeRanges)
-> JSM (Maybe JSVal) -> JSM (Maybe TimeRanges)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TimeRanges
fromJSValUnchecked = TimeRanges -> JSM TimeRanges
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TimeRanges -> JSM TimeRanges)
-> (JSVal -> TimeRanges) -> JSVal -> JSM TimeRanges
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TimeRanges
TimeRanges
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TimeRanges where
  makeObject :: TimeRanges -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TimeRanges -> JSVal) -> TimeRanges -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeRanges -> JSVal
unTimeRanges

instance IsGObject TimeRanges where
  typeGType :: TimeRanges -> JSM GType
typeGType TimeRanges
_ = JSM GType
gTypeTimeRanges
  {-# INLINE typeGType #-}

noTimeRanges :: Maybe TimeRanges
noTimeRanges :: Maybe TimeRanges
noTimeRanges = Maybe TimeRanges
forall a. Maybe a
Nothing
{-# INLINE noTimeRanges #-}

gTypeTimeRanges :: JSM GType
gTypeTimeRanges :: JSM GType
gTypeTimeRanges = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TimeRanges"

-- | Functions for this inteface are in "JSDOM.Touch".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Touch Mozilla Touch documentation>
newtype Touch = Touch { Touch -> JSVal
unTouch :: JSVal }

instance PToJSVal Touch where
  pToJSVal :: Touch -> JSVal
pToJSVal = Touch -> JSVal
unTouch
  {-# INLINE pToJSVal #-}

instance PFromJSVal Touch where
  pFromJSVal :: JSVal -> Touch
pFromJSVal = JSVal -> Touch
Touch
  {-# INLINE pFromJSVal #-}

instance ToJSVal Touch where
  toJSVal :: Touch -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Touch -> JSVal) -> Touch -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Touch -> JSVal
unTouch
  {-# INLINE toJSVal #-}

instance FromJSVal Touch where
  fromJSVal :: JSVal -> JSM (Maybe Touch)
fromJSVal JSVal
v = (JSVal -> Touch) -> Maybe JSVal -> Maybe Touch
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Touch
Touch (Maybe JSVal -> Maybe Touch)
-> JSM (Maybe JSVal) -> JSM (Maybe Touch)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Touch
fromJSValUnchecked = Touch -> JSM Touch
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Touch -> JSM Touch) -> (JSVal -> Touch) -> JSVal -> JSM Touch
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Touch
Touch
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Touch where
  makeObject :: Touch -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Touch -> JSVal) -> Touch -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Touch -> JSVal
unTouch

instance IsGObject Touch where
  typeGType :: Touch -> JSM GType
typeGType Touch
_ = JSM GType
gTypeTouch
  {-# INLINE typeGType #-}

noTouch :: Maybe Touch
noTouch :: Maybe Touch
noTouch = Maybe Touch
forall a. Maybe a
Nothing
{-# INLINE noTouch #-}

gTypeTouch :: JSM GType
gTypeTouch :: JSM GType
gTypeTouch = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Touch"

-- | Functions for this inteface are in "JSDOM.TouchEvent".
-- Base interface functions are in:
--
--     * "JSDOM.UIEvent"
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TouchEvent Mozilla TouchEvent documentation>
newtype TouchEvent = TouchEvent { TouchEvent -> JSVal
unTouchEvent :: JSVal }

instance PToJSVal TouchEvent where
  pToJSVal :: TouchEvent -> JSVal
pToJSVal = TouchEvent -> JSVal
unTouchEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal TouchEvent where
  pFromJSVal :: JSVal -> TouchEvent
pFromJSVal = JSVal -> TouchEvent
TouchEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal TouchEvent where
  toJSVal :: TouchEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TouchEvent -> JSVal) -> TouchEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TouchEvent -> JSVal
unTouchEvent
  {-# INLINE toJSVal #-}

instance FromJSVal TouchEvent where
  fromJSVal :: JSVal -> JSM (Maybe TouchEvent)
fromJSVal JSVal
v = (JSVal -> TouchEvent) -> Maybe JSVal -> Maybe TouchEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TouchEvent
TouchEvent (Maybe JSVal -> Maybe TouchEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe TouchEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TouchEvent
fromJSValUnchecked = TouchEvent -> JSM TouchEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TouchEvent -> JSM TouchEvent)
-> (JSVal -> TouchEvent) -> JSVal -> JSM TouchEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TouchEvent
TouchEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TouchEvent where
  makeObject :: TouchEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TouchEvent -> JSVal) -> TouchEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TouchEvent -> JSVal
unTouchEvent

instance IsUIEvent TouchEvent
instance IsEvent TouchEvent
instance IsGObject TouchEvent where
  typeGType :: TouchEvent -> JSM GType
typeGType TouchEvent
_ = JSM GType
gTypeTouchEvent
  {-# INLINE typeGType #-}

noTouchEvent :: Maybe TouchEvent
noTouchEvent :: Maybe TouchEvent
noTouchEvent = Maybe TouchEvent
forall a. Maybe a
Nothing
{-# INLINE noTouchEvent #-}

gTypeTouchEvent :: JSM GType
gTypeTouchEvent :: JSM GType
gTypeTouchEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TouchEvent"

-- | Functions for this inteface are in "JSDOM.TouchEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.UIEventInit"
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TouchEventInit Mozilla TouchEventInit documentation>
newtype TouchEventInit = TouchEventInit { TouchEventInit -> JSVal
unTouchEventInit :: JSVal }

instance PToJSVal TouchEventInit where
  pToJSVal :: TouchEventInit -> JSVal
pToJSVal = TouchEventInit -> JSVal
unTouchEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal TouchEventInit where
  pFromJSVal :: JSVal -> TouchEventInit
pFromJSVal = JSVal -> TouchEventInit
TouchEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal TouchEventInit where
  toJSVal :: TouchEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TouchEventInit -> JSVal) -> TouchEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TouchEventInit -> JSVal
unTouchEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal TouchEventInit where
  fromJSVal :: JSVal -> JSM (Maybe TouchEventInit)
fromJSVal JSVal
v = (JSVal -> TouchEventInit) -> Maybe JSVal -> Maybe TouchEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TouchEventInit
TouchEventInit (Maybe JSVal -> Maybe TouchEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe TouchEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TouchEventInit
fromJSValUnchecked = TouchEventInit -> JSM TouchEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TouchEventInit -> JSM TouchEventInit)
-> (JSVal -> TouchEventInit) -> JSVal -> JSM TouchEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TouchEventInit
TouchEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TouchEventInit where
  makeObject :: TouchEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TouchEventInit -> JSVal) -> TouchEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TouchEventInit -> JSVal
unTouchEventInit

instance IsUIEventInit TouchEventInit
instance IsEventInit TouchEventInit
instance IsGObject TouchEventInit where
  typeGType :: TouchEventInit -> JSM GType
typeGType TouchEventInit
_ = JSM GType
gTypeTouchEventInit
  {-# INLINE typeGType #-}

noTouchEventInit :: Maybe TouchEventInit
noTouchEventInit :: Maybe TouchEventInit
noTouchEventInit = Maybe TouchEventInit
forall a. Maybe a
Nothing
{-# INLINE noTouchEventInit #-}

gTypeTouchEventInit :: JSM GType
gTypeTouchEventInit :: JSM GType
gTypeTouchEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TouchEventInit"

-- | Functions for this inteface are in "JSDOM.TouchList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TouchList Mozilla TouchList documentation>
newtype TouchList = TouchList { TouchList -> JSVal
unTouchList :: JSVal }

instance PToJSVal TouchList where
  pToJSVal :: TouchList -> JSVal
pToJSVal = TouchList -> JSVal
unTouchList
  {-# INLINE pToJSVal #-}

instance PFromJSVal TouchList where
  pFromJSVal :: JSVal -> TouchList
pFromJSVal = JSVal -> TouchList
TouchList
  {-# INLINE pFromJSVal #-}

instance ToJSVal TouchList where
  toJSVal :: TouchList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TouchList -> JSVal) -> TouchList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TouchList -> JSVal
unTouchList
  {-# INLINE toJSVal #-}

instance FromJSVal TouchList where
  fromJSVal :: JSVal -> JSM (Maybe TouchList)
fromJSVal JSVal
v = (JSVal -> TouchList) -> Maybe JSVal -> Maybe TouchList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TouchList
TouchList (Maybe JSVal -> Maybe TouchList)
-> JSM (Maybe JSVal) -> JSM (Maybe TouchList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TouchList
fromJSValUnchecked = TouchList -> JSM TouchList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TouchList -> JSM TouchList)
-> (JSVal -> TouchList) -> JSVal -> JSM TouchList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TouchList
TouchList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TouchList where
  makeObject :: TouchList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TouchList -> JSVal) -> TouchList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TouchList -> JSVal
unTouchList

instance IsGObject TouchList where
  typeGType :: TouchList -> JSM GType
typeGType TouchList
_ = JSM GType
gTypeTouchList
  {-# INLINE typeGType #-}

noTouchList :: Maybe TouchList
noTouchList :: Maybe TouchList
noTouchList = Maybe TouchList
forall a. Maybe a
Nothing
{-# INLINE noTouchList #-}

gTypeTouchList :: JSM GType
gTypeTouchList :: JSM GType
gTypeTouchList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TouchList"

-- | Functions for this inteface are in "JSDOM.TrackEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TrackEvent Mozilla TrackEvent documentation>
newtype TrackEvent = TrackEvent { TrackEvent -> JSVal
unTrackEvent :: JSVal }

instance PToJSVal TrackEvent where
  pToJSVal :: TrackEvent -> JSVal
pToJSVal = TrackEvent -> JSVal
unTrackEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal TrackEvent where
  pFromJSVal :: JSVal -> TrackEvent
pFromJSVal = JSVal -> TrackEvent
TrackEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal TrackEvent where
  toJSVal :: TrackEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TrackEvent -> JSVal) -> TrackEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TrackEvent -> JSVal
unTrackEvent
  {-# INLINE toJSVal #-}

instance FromJSVal TrackEvent where
  fromJSVal :: JSVal -> JSM (Maybe TrackEvent)
fromJSVal JSVal
v = (JSVal -> TrackEvent) -> Maybe JSVal -> Maybe TrackEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TrackEvent
TrackEvent (Maybe JSVal -> Maybe TrackEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe TrackEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TrackEvent
fromJSValUnchecked = TrackEvent -> JSM TrackEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TrackEvent -> JSM TrackEvent)
-> (JSVal -> TrackEvent) -> JSVal -> JSM TrackEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TrackEvent
TrackEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TrackEvent where
  makeObject :: TrackEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TrackEvent -> JSVal) -> TrackEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TrackEvent -> JSVal
unTrackEvent

instance IsEvent TrackEvent
instance IsGObject TrackEvent where
  typeGType :: TrackEvent -> JSM GType
typeGType TrackEvent
_ = JSM GType
gTypeTrackEvent
  {-# INLINE typeGType #-}

noTrackEvent :: Maybe TrackEvent
noTrackEvent :: Maybe TrackEvent
noTrackEvent = Maybe TrackEvent
forall a. Maybe a
Nothing
{-# INLINE noTrackEvent #-}

gTypeTrackEvent :: JSM GType
gTypeTrackEvent :: JSM GType
gTypeTrackEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TrackEvent"

-- | Functions for this inteface are in "JSDOM.TrackEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TrackEventInit Mozilla TrackEventInit documentation>
newtype TrackEventInit = TrackEventInit { TrackEventInit -> JSVal
unTrackEventInit :: JSVal }

instance PToJSVal TrackEventInit where
  pToJSVal :: TrackEventInit -> JSVal
pToJSVal = TrackEventInit -> JSVal
unTrackEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal TrackEventInit where
  pFromJSVal :: JSVal -> TrackEventInit
pFromJSVal = JSVal -> TrackEventInit
TrackEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal TrackEventInit where
  toJSVal :: TrackEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TrackEventInit -> JSVal) -> TrackEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TrackEventInit -> JSVal
unTrackEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal TrackEventInit where
  fromJSVal :: JSVal -> JSM (Maybe TrackEventInit)
fromJSVal JSVal
v = (JSVal -> TrackEventInit) -> Maybe JSVal -> Maybe TrackEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TrackEventInit
TrackEventInit (Maybe JSVal -> Maybe TrackEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe TrackEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TrackEventInit
fromJSValUnchecked = TrackEventInit -> JSM TrackEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TrackEventInit -> JSM TrackEventInit)
-> (JSVal -> TrackEventInit) -> JSVal -> JSM TrackEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TrackEventInit
TrackEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TrackEventInit where
  makeObject :: TrackEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TrackEventInit -> JSVal) -> TrackEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TrackEventInit -> JSVal
unTrackEventInit

instance IsEventInit TrackEventInit
instance IsGObject TrackEventInit where
  typeGType :: TrackEventInit -> JSM GType
typeGType TrackEventInit
_ = JSM GType
gTypeTrackEventInit
  {-# INLINE typeGType #-}

noTrackEventInit :: Maybe TrackEventInit
noTrackEventInit :: Maybe TrackEventInit
noTrackEventInit = Maybe TrackEventInit
forall a. Maybe a
Nothing
{-# INLINE noTrackEventInit #-}

gTypeTrackEventInit :: JSM GType
gTypeTrackEventInit :: JSM GType
gTypeTrackEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TrackEventInit"

-- | Functions for this inteface are in "JSDOM.TransitionEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TransitionEvent Mozilla TransitionEvent documentation>
newtype TransitionEvent = TransitionEvent { TransitionEvent -> JSVal
unTransitionEvent :: JSVal }

instance PToJSVal TransitionEvent where
  pToJSVal :: TransitionEvent -> JSVal
pToJSVal = TransitionEvent -> JSVal
unTransitionEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal TransitionEvent where
  pFromJSVal :: JSVal -> TransitionEvent
pFromJSVal = JSVal -> TransitionEvent
TransitionEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal TransitionEvent where
  toJSVal :: TransitionEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TransitionEvent -> JSVal) -> TransitionEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TransitionEvent -> JSVal
unTransitionEvent
  {-# INLINE toJSVal #-}

instance FromJSVal TransitionEvent where
  fromJSVal :: JSVal -> JSM (Maybe TransitionEvent)
fromJSVal JSVal
v = (JSVal -> TransitionEvent) -> Maybe JSVal -> Maybe TransitionEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TransitionEvent
TransitionEvent (Maybe JSVal -> Maybe TransitionEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe TransitionEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TransitionEvent
fromJSValUnchecked = TransitionEvent -> JSM TransitionEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TransitionEvent -> JSM TransitionEvent)
-> (JSVal -> TransitionEvent) -> JSVal -> JSM TransitionEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TransitionEvent
TransitionEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TransitionEvent where
  makeObject :: TransitionEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TransitionEvent -> JSVal) -> TransitionEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TransitionEvent -> JSVal
unTransitionEvent

instance IsEvent TransitionEvent
instance IsGObject TransitionEvent where
  typeGType :: TransitionEvent -> JSM GType
typeGType TransitionEvent
_ = JSM GType
gTypeTransitionEvent
  {-# INLINE typeGType #-}

noTransitionEvent :: Maybe TransitionEvent
noTransitionEvent :: Maybe TransitionEvent
noTransitionEvent = Maybe TransitionEvent
forall a. Maybe a
Nothing
{-# INLINE noTransitionEvent #-}

gTypeTransitionEvent :: JSM GType
gTypeTransitionEvent :: JSM GType
gTypeTransitionEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TransitionEvent"

-- | Functions for this inteface are in "JSDOM.TransitionEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TransitionEventInit Mozilla TransitionEventInit documentation>
newtype TransitionEventInit = TransitionEventInit { TransitionEventInit -> JSVal
unTransitionEventInit :: JSVal }

instance PToJSVal TransitionEventInit where
  pToJSVal :: TransitionEventInit -> JSVal
pToJSVal = TransitionEventInit -> JSVal
unTransitionEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal TransitionEventInit where
  pFromJSVal :: JSVal -> TransitionEventInit
pFromJSVal = JSVal -> TransitionEventInit
TransitionEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal TransitionEventInit where
  toJSVal :: TransitionEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TransitionEventInit -> JSVal)
-> TransitionEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TransitionEventInit -> JSVal
unTransitionEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal TransitionEventInit where
  fromJSVal :: JSVal -> JSM (Maybe TransitionEventInit)
fromJSVal JSVal
v = (JSVal -> TransitionEventInit)
-> Maybe JSVal -> Maybe TransitionEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TransitionEventInit
TransitionEventInit (Maybe JSVal -> Maybe TransitionEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe TransitionEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TransitionEventInit
fromJSValUnchecked = TransitionEventInit -> JSM TransitionEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TransitionEventInit -> JSM TransitionEventInit)
-> (JSVal -> TransitionEventInit)
-> JSVal
-> JSM TransitionEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TransitionEventInit
TransitionEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TransitionEventInit where
  makeObject :: TransitionEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TransitionEventInit -> JSVal)
-> TransitionEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TransitionEventInit -> JSVal
unTransitionEventInit

instance IsEventInit TransitionEventInit
instance IsGObject TransitionEventInit where
  typeGType :: TransitionEventInit -> JSM GType
typeGType TransitionEventInit
_ = JSM GType
gTypeTransitionEventInit
  {-# INLINE typeGType #-}

noTransitionEventInit :: Maybe TransitionEventInit
noTransitionEventInit :: Maybe TransitionEventInit
noTransitionEventInit = Maybe TransitionEventInit
forall a. Maybe a
Nothing
{-# INLINE noTransitionEventInit #-}

gTypeTransitionEventInit :: JSM GType
gTypeTransitionEventInit :: JSM GType
gTypeTransitionEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TransitionEventInit"

-- | Functions for this inteface are in "JSDOM.TreeWalker".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/TreeWalker Mozilla TreeWalker documentation>
newtype TreeWalker = TreeWalker { TreeWalker -> JSVal
unTreeWalker :: JSVal }

instance PToJSVal TreeWalker where
  pToJSVal :: TreeWalker -> JSVal
pToJSVal = TreeWalker -> JSVal
unTreeWalker
  {-# INLINE pToJSVal #-}

instance PFromJSVal TreeWalker where
  pFromJSVal :: JSVal -> TreeWalker
pFromJSVal = JSVal -> TreeWalker
TreeWalker
  {-# INLINE pFromJSVal #-}

instance ToJSVal TreeWalker where
  toJSVal :: TreeWalker -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (TreeWalker -> JSVal) -> TreeWalker -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TreeWalker -> JSVal
unTreeWalker
  {-# INLINE toJSVal #-}

instance FromJSVal TreeWalker where
  fromJSVal :: JSVal -> JSM (Maybe TreeWalker)
fromJSVal JSVal
v = (JSVal -> TreeWalker) -> Maybe JSVal -> Maybe TreeWalker
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> TreeWalker
TreeWalker (Maybe JSVal -> Maybe TreeWalker)
-> JSM (Maybe JSVal) -> JSM (Maybe TreeWalker)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM TreeWalker
fromJSValUnchecked = TreeWalker -> JSM TreeWalker
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TreeWalker -> JSM TreeWalker)
-> (JSVal -> TreeWalker) -> JSVal -> JSM TreeWalker
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> TreeWalker
TreeWalker
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject TreeWalker where
  makeObject :: TreeWalker -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (TreeWalker -> JSVal) -> TreeWalker -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TreeWalker -> JSVal
unTreeWalker

instance IsGObject TreeWalker where
  typeGType :: TreeWalker -> JSM GType
typeGType TreeWalker
_ = JSM GType
gTypeTreeWalker
  {-# INLINE typeGType #-}

noTreeWalker :: Maybe TreeWalker
noTreeWalker :: Maybe TreeWalker
noTreeWalker = Maybe TreeWalker
forall a. Maybe a
Nothing
{-# INLINE noTreeWalker #-}

gTypeTreeWalker :: JSM GType
gTypeTreeWalker :: JSM GType
gTypeTreeWalker = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"TreeWalker"

-- | Functions for this inteface are in "JSDOM.UIEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/UIEvent Mozilla UIEvent documentation>
newtype UIEvent = UIEvent { UIEvent -> JSVal
unUIEvent :: JSVal }

instance PToJSVal UIEvent where
  pToJSVal :: UIEvent -> JSVal
pToJSVal = UIEvent -> JSVal
unUIEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal UIEvent where
  pFromJSVal :: JSVal -> UIEvent
pFromJSVal = JSVal -> UIEvent
UIEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal UIEvent where
  toJSVal :: UIEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (UIEvent -> JSVal) -> UIEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UIEvent -> JSVal
unUIEvent
  {-# INLINE toJSVal #-}

instance FromJSVal UIEvent where
  fromJSVal :: JSVal -> JSM (Maybe UIEvent)
fromJSVal JSVal
v = (JSVal -> UIEvent) -> Maybe JSVal -> Maybe UIEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> UIEvent
UIEvent (Maybe JSVal -> Maybe UIEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe UIEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM UIEvent
fromJSValUnchecked = UIEvent -> JSM UIEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (UIEvent -> JSM UIEvent)
-> (JSVal -> UIEvent) -> JSVal -> JSM UIEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> UIEvent
UIEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject UIEvent where
  makeObject :: UIEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (UIEvent -> JSVal) -> UIEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UIEvent -> JSVal
unUIEvent

class (IsEvent o, IsGObject o) => IsUIEvent o
toUIEvent :: IsUIEvent o => o -> UIEvent
toUIEvent :: forall o. IsUIEvent o => o -> UIEvent
toUIEvent = JSVal -> UIEvent
UIEvent (JSVal -> UIEvent) -> (o -> JSVal) -> o -> UIEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsUIEvent UIEvent
instance IsEvent UIEvent
instance IsGObject UIEvent where
  typeGType :: UIEvent -> JSM GType
typeGType UIEvent
_ = JSM GType
gTypeUIEvent
  {-# INLINE typeGType #-}

noUIEvent :: Maybe UIEvent
noUIEvent :: Maybe UIEvent
noUIEvent = Maybe UIEvent
forall a. Maybe a
Nothing
{-# INLINE noUIEvent #-}

gTypeUIEvent :: JSM GType
gTypeUIEvent :: JSM GType
gTypeUIEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"UIEvent"

-- | Functions for this inteface are in "JSDOM.UIEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/UIEventInit Mozilla UIEventInit documentation>
newtype UIEventInit = UIEventInit { UIEventInit -> JSVal
unUIEventInit :: JSVal }

instance PToJSVal UIEventInit where
  pToJSVal :: UIEventInit -> JSVal
pToJSVal = UIEventInit -> JSVal
unUIEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal UIEventInit where
  pFromJSVal :: JSVal -> UIEventInit
pFromJSVal = JSVal -> UIEventInit
UIEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal UIEventInit where
  toJSVal :: UIEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (UIEventInit -> JSVal) -> UIEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UIEventInit -> JSVal
unUIEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal UIEventInit where
  fromJSVal :: JSVal -> JSM (Maybe UIEventInit)
fromJSVal JSVal
v = (JSVal -> UIEventInit) -> Maybe JSVal -> Maybe UIEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> UIEventInit
UIEventInit (Maybe JSVal -> Maybe UIEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe UIEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM UIEventInit
fromJSValUnchecked = UIEventInit -> JSM UIEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (UIEventInit -> JSM UIEventInit)
-> (JSVal -> UIEventInit) -> JSVal -> JSM UIEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> UIEventInit
UIEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject UIEventInit where
  makeObject :: UIEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (UIEventInit -> JSVal) -> UIEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UIEventInit -> JSVal
unUIEventInit

class (IsEventInit o, IsGObject o) => IsUIEventInit o
toUIEventInit :: IsUIEventInit o => o -> UIEventInit
toUIEventInit :: forall o. IsUIEventInit o => o -> UIEventInit
toUIEventInit = JSVal -> UIEventInit
UIEventInit (JSVal -> UIEventInit) -> (o -> JSVal) -> o -> UIEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsUIEventInit UIEventInit
instance IsEventInit UIEventInit
instance IsGObject UIEventInit where
  typeGType :: UIEventInit -> JSM GType
typeGType UIEventInit
_ = JSM GType
gTypeUIEventInit
  {-# INLINE typeGType #-}

noUIEventInit :: Maybe UIEventInit
noUIEventInit :: Maybe UIEventInit
noUIEventInit = Maybe UIEventInit
forall a. Maybe a
Nothing
{-# INLINE noUIEventInit #-}

gTypeUIEventInit :: JSM GType
gTypeUIEventInit :: JSM GType
gTypeUIEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"UIEventInit"

-- | Functions for this inteface are in "JSDOM.URL".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/URL Mozilla URL documentation>
newtype URL = URL { URL -> JSVal
unURL :: JSVal }

instance PToJSVal URL where
  pToJSVal :: URL -> JSVal
pToJSVal = URL -> JSVal
unURL
  {-# INLINE pToJSVal #-}

instance PFromJSVal URL where
  pFromJSVal :: JSVal -> URL
pFromJSVal = JSVal -> URL
URL
  {-# INLINE pFromJSVal #-}

instance ToJSVal URL where
  toJSVal :: URL -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (URL -> JSVal) -> URL -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URL -> JSVal
unURL
  {-# INLINE toJSVal #-}

instance FromJSVal URL where
  fromJSVal :: JSVal -> JSM (Maybe URL)
fromJSVal JSVal
v = (JSVal -> URL) -> Maybe JSVal -> Maybe URL
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> URL
URL (Maybe JSVal -> Maybe URL) -> JSM (Maybe JSVal) -> JSM (Maybe URL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM URL
fromJSValUnchecked = URL -> JSM URL
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (URL -> JSM URL) -> (JSVal -> URL) -> JSVal -> JSM URL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> URL
URL
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject URL where
  makeObject :: URL -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (URL -> JSVal) -> URL -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URL -> JSVal
unURL

instance IsGObject URL where
  typeGType :: URL -> JSM GType
typeGType URL
_ = JSM GType
gTypeURL
  {-# INLINE typeGType #-}

noURL :: Maybe URL
noURL :: Maybe URL
noURL = Maybe URL
forall a. Maybe a
Nothing
{-# INLINE noURL #-}

gTypeURL :: JSM GType
gTypeURL :: JSM GType
gTypeURL = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"URL"

-- | Functions for this inteface are in "JSDOM.URLSearchParams".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/URLSearchParams Mozilla URLSearchParams documentation>
newtype URLSearchParams = URLSearchParams { URLSearchParams -> JSVal
unURLSearchParams :: JSVal }

instance PToJSVal URLSearchParams where
  pToJSVal :: URLSearchParams -> JSVal
pToJSVal = URLSearchParams -> JSVal
unURLSearchParams
  {-# INLINE pToJSVal #-}

instance PFromJSVal URLSearchParams where
  pFromJSVal :: JSVal -> URLSearchParams
pFromJSVal = JSVal -> URLSearchParams
URLSearchParams
  {-# INLINE pFromJSVal #-}

instance ToJSVal URLSearchParams where
  toJSVal :: URLSearchParams -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (URLSearchParams -> JSVal) -> URLSearchParams -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URLSearchParams -> JSVal
unURLSearchParams
  {-# INLINE toJSVal #-}

instance FromJSVal URLSearchParams where
  fromJSVal :: JSVal -> JSM (Maybe URLSearchParams)
fromJSVal JSVal
v = (JSVal -> URLSearchParams) -> Maybe JSVal -> Maybe URLSearchParams
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> URLSearchParams
URLSearchParams (Maybe JSVal -> Maybe URLSearchParams)
-> JSM (Maybe JSVal) -> JSM (Maybe URLSearchParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM URLSearchParams
fromJSValUnchecked = URLSearchParams -> JSM URLSearchParams
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (URLSearchParams -> JSM URLSearchParams)
-> (JSVal -> URLSearchParams) -> JSVal -> JSM URLSearchParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> URLSearchParams
URLSearchParams
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject URLSearchParams where
  makeObject :: URLSearchParams -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (URLSearchParams -> JSVal) -> URLSearchParams -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URLSearchParams -> JSVal
unURLSearchParams

instance IsGObject URLSearchParams where
  typeGType :: URLSearchParams -> JSM GType
typeGType URLSearchParams
_ = JSM GType
gTypeURLSearchParams
  {-# INLINE typeGType #-}

noURLSearchParams :: Maybe URLSearchParams
noURLSearchParams :: Maybe URLSearchParams
noURLSearchParams = Maybe URLSearchParams
forall a. Maybe a
Nothing
{-# INLINE noURLSearchParams #-}

gTypeURLSearchParams :: JSM GType
gTypeURLSearchParams :: JSM GType
gTypeURLSearchParams = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"URLSearchParams"

-- | Functions for this inteface are in "JSDOM.UserMessageHandler".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/UserMessageHandler Mozilla UserMessageHandler documentation>
newtype UserMessageHandler = UserMessageHandler { UserMessageHandler -> JSVal
unUserMessageHandler :: JSVal }

instance PToJSVal UserMessageHandler where
  pToJSVal :: UserMessageHandler -> JSVal
pToJSVal = UserMessageHandler -> JSVal
unUserMessageHandler
  {-# INLINE pToJSVal #-}

instance PFromJSVal UserMessageHandler where
  pFromJSVal :: JSVal -> UserMessageHandler
pFromJSVal = JSVal -> UserMessageHandler
UserMessageHandler
  {-# INLINE pFromJSVal #-}

instance ToJSVal UserMessageHandler where
  toJSVal :: UserMessageHandler -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (UserMessageHandler -> JSVal) -> UserMessageHandler -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UserMessageHandler -> JSVal
unUserMessageHandler
  {-# INLINE toJSVal #-}

instance FromJSVal UserMessageHandler where
  fromJSVal :: JSVal -> JSM (Maybe UserMessageHandler)
fromJSVal JSVal
v = (JSVal -> UserMessageHandler)
-> Maybe JSVal -> Maybe UserMessageHandler
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> UserMessageHandler
UserMessageHandler (Maybe JSVal -> Maybe UserMessageHandler)
-> JSM (Maybe JSVal) -> JSM (Maybe UserMessageHandler)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM UserMessageHandler
fromJSValUnchecked = UserMessageHandler -> JSM UserMessageHandler
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (UserMessageHandler -> JSM UserMessageHandler)
-> (JSVal -> UserMessageHandler) -> JSVal -> JSM UserMessageHandler
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> UserMessageHandler
UserMessageHandler
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject UserMessageHandler where
  makeObject :: UserMessageHandler -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (UserMessageHandler -> JSVal)
-> UserMessageHandler
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UserMessageHandler -> JSVal
unUserMessageHandler

instance IsGObject UserMessageHandler where
  typeGType :: UserMessageHandler -> JSM GType
typeGType UserMessageHandler
_ = JSM GType
gTypeUserMessageHandler
  {-# INLINE typeGType #-}

noUserMessageHandler :: Maybe UserMessageHandler
noUserMessageHandler :: Maybe UserMessageHandler
noUserMessageHandler = Maybe UserMessageHandler
forall a. Maybe a
Nothing
{-# INLINE noUserMessageHandler #-}

gTypeUserMessageHandler :: JSM GType
gTypeUserMessageHandler :: JSM GType
gTypeUserMessageHandler = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"UserMessageHandler"

-- | Functions for this inteface are in "JSDOM.UserMessageHandlersNamespace".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/UserMessageHandlersNamespace Mozilla UserMessageHandlersNamespace documentation>
newtype UserMessageHandlersNamespace = UserMessageHandlersNamespace { UserMessageHandlersNamespace -> JSVal
unUserMessageHandlersNamespace :: JSVal }

instance PToJSVal UserMessageHandlersNamespace where
  pToJSVal :: UserMessageHandlersNamespace -> JSVal
pToJSVal = UserMessageHandlersNamespace -> JSVal
unUserMessageHandlersNamespace
  {-# INLINE pToJSVal #-}

instance PFromJSVal UserMessageHandlersNamespace where
  pFromJSVal :: JSVal -> UserMessageHandlersNamespace
pFromJSVal = JSVal -> UserMessageHandlersNamespace
UserMessageHandlersNamespace
  {-# INLINE pFromJSVal #-}

instance ToJSVal UserMessageHandlersNamespace where
  toJSVal :: UserMessageHandlersNamespace -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (UserMessageHandlersNamespace -> JSVal)
-> UserMessageHandlersNamespace
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UserMessageHandlersNamespace -> JSVal
unUserMessageHandlersNamespace
  {-# INLINE toJSVal #-}

instance FromJSVal UserMessageHandlersNamespace where
  fromJSVal :: JSVal -> JSM (Maybe UserMessageHandlersNamespace)
fromJSVal JSVal
v = (JSVal -> UserMessageHandlersNamespace)
-> Maybe JSVal -> Maybe UserMessageHandlersNamespace
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> UserMessageHandlersNamespace
UserMessageHandlersNamespace (Maybe JSVal -> Maybe UserMessageHandlersNamespace)
-> JSM (Maybe JSVal) -> JSM (Maybe UserMessageHandlersNamespace)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM UserMessageHandlersNamespace
fromJSValUnchecked = UserMessageHandlersNamespace -> JSM UserMessageHandlersNamespace
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (UserMessageHandlersNamespace -> JSM UserMessageHandlersNamespace)
-> (JSVal -> UserMessageHandlersNamespace)
-> JSVal
-> JSM UserMessageHandlersNamespace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> UserMessageHandlersNamespace
UserMessageHandlersNamespace
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject UserMessageHandlersNamespace where
  makeObject :: UserMessageHandlersNamespace -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (UserMessageHandlersNamespace -> JSVal)
-> UserMessageHandlersNamespace
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UserMessageHandlersNamespace -> JSVal
unUserMessageHandlersNamespace

instance IsGObject UserMessageHandlersNamespace where
  typeGType :: UserMessageHandlersNamespace -> JSM GType
typeGType UserMessageHandlersNamespace
_ = JSM GType
gTypeUserMessageHandlersNamespace
  {-# INLINE typeGType #-}

noUserMessageHandlersNamespace :: Maybe UserMessageHandlersNamespace
noUserMessageHandlersNamespace :: Maybe UserMessageHandlersNamespace
noUserMessageHandlersNamespace = Maybe UserMessageHandlersNamespace
forall a. Maybe a
Nothing
{-# INLINE noUserMessageHandlersNamespace #-}

gTypeUserMessageHandlersNamespace :: JSM GType
gTypeUserMessageHandlersNamespace :: JSM GType
gTypeUserMessageHandlersNamespace = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"UserMessageHandlersNamespace"

-- | Functions for this inteface are in "JSDOM.VTTCue".
-- Base interface functions are in:
--
--     * "JSDOM.TextTrackCue"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/VTTCue Mozilla VTTCue documentation>
newtype VTTCue = VTTCue { VTTCue -> JSVal
unVTTCue :: JSVal }

instance PToJSVal VTTCue where
  pToJSVal :: VTTCue -> JSVal
pToJSVal = VTTCue -> JSVal
unVTTCue
  {-# INLINE pToJSVal #-}

instance PFromJSVal VTTCue where
  pFromJSVal :: JSVal -> VTTCue
pFromJSVal = JSVal -> VTTCue
VTTCue
  {-# INLINE pFromJSVal #-}

instance ToJSVal VTTCue where
  toJSVal :: VTTCue -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (VTTCue -> JSVal) -> VTTCue -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VTTCue -> JSVal
unVTTCue
  {-# INLINE toJSVal #-}

instance FromJSVal VTTCue where
  fromJSVal :: JSVal -> JSM (Maybe VTTCue)
fromJSVal JSVal
v = (JSVal -> VTTCue) -> Maybe JSVal -> Maybe VTTCue
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> VTTCue
VTTCue (Maybe JSVal -> Maybe VTTCue)
-> JSM (Maybe JSVal) -> JSM (Maybe VTTCue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM VTTCue
fromJSValUnchecked = VTTCue -> JSM VTTCue
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (VTTCue -> JSM VTTCue) -> (JSVal -> VTTCue) -> JSVal -> JSM VTTCue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> VTTCue
VTTCue
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject VTTCue where
  makeObject :: VTTCue -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (VTTCue -> JSVal) -> VTTCue -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VTTCue -> JSVal
unVTTCue

instance IsTextTrackCue VTTCue
instance IsEventTarget VTTCue
instance IsGObject VTTCue where
  typeGType :: VTTCue -> JSM GType
typeGType VTTCue
_ = JSM GType
gTypeVTTCue
  {-# INLINE typeGType #-}

noVTTCue :: Maybe VTTCue
noVTTCue :: Maybe VTTCue
noVTTCue = Maybe VTTCue
forall a. Maybe a
Nothing
{-# INLINE noVTTCue #-}

gTypeVTTCue :: JSM GType
gTypeVTTCue :: JSM GType
gTypeVTTCue = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"VTTCue"

-- | Functions for this inteface are in "JSDOM.VTTRegion".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/VTTRegion Mozilla VTTRegion documentation>
newtype VTTRegion = VTTRegion { VTTRegion -> JSVal
unVTTRegion :: JSVal }

instance PToJSVal VTTRegion where
  pToJSVal :: VTTRegion -> JSVal
pToJSVal = VTTRegion -> JSVal
unVTTRegion
  {-# INLINE pToJSVal #-}

instance PFromJSVal VTTRegion where
  pFromJSVal :: JSVal -> VTTRegion
pFromJSVal = JSVal -> VTTRegion
VTTRegion
  {-# INLINE pFromJSVal #-}

instance ToJSVal VTTRegion where
  toJSVal :: VTTRegion -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (VTTRegion -> JSVal) -> VTTRegion -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VTTRegion -> JSVal
unVTTRegion
  {-# INLINE toJSVal #-}

instance FromJSVal VTTRegion where
  fromJSVal :: JSVal -> JSM (Maybe VTTRegion)
fromJSVal JSVal
v = (JSVal -> VTTRegion) -> Maybe JSVal -> Maybe VTTRegion
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> VTTRegion
VTTRegion (Maybe JSVal -> Maybe VTTRegion)
-> JSM (Maybe JSVal) -> JSM (Maybe VTTRegion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM VTTRegion
fromJSValUnchecked = VTTRegion -> JSM VTTRegion
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (VTTRegion -> JSM VTTRegion)
-> (JSVal -> VTTRegion) -> JSVal -> JSM VTTRegion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> VTTRegion
VTTRegion
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject VTTRegion where
  makeObject :: VTTRegion -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (VTTRegion -> JSVal) -> VTTRegion -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VTTRegion -> JSVal
unVTTRegion

instance IsGObject VTTRegion where
  typeGType :: VTTRegion -> JSM GType
typeGType VTTRegion
_ = JSM GType
gTypeVTTRegion
  {-# INLINE typeGType #-}

noVTTRegion :: Maybe VTTRegion
noVTTRegion :: Maybe VTTRegion
noVTTRegion = Maybe VTTRegion
forall a. Maybe a
Nothing
{-# INLINE noVTTRegion #-}

gTypeVTTRegion :: JSM GType
gTypeVTTRegion :: JSM GType
gTypeVTTRegion = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"VTTRegion"

-- | Functions for this inteface are in "JSDOM.VTTRegionList".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/VTTRegionList Mozilla VTTRegionList documentation>
newtype VTTRegionList = VTTRegionList { VTTRegionList -> JSVal
unVTTRegionList :: JSVal }

instance PToJSVal VTTRegionList where
  pToJSVal :: VTTRegionList -> JSVal
pToJSVal = VTTRegionList -> JSVal
unVTTRegionList
  {-# INLINE pToJSVal #-}

instance PFromJSVal VTTRegionList where
  pFromJSVal :: JSVal -> VTTRegionList
pFromJSVal = JSVal -> VTTRegionList
VTTRegionList
  {-# INLINE pFromJSVal #-}

instance ToJSVal VTTRegionList where
  toJSVal :: VTTRegionList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (VTTRegionList -> JSVal) -> VTTRegionList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VTTRegionList -> JSVal
unVTTRegionList
  {-# INLINE toJSVal #-}

instance FromJSVal VTTRegionList where
  fromJSVal :: JSVal -> JSM (Maybe VTTRegionList)
fromJSVal JSVal
v = (JSVal -> VTTRegionList) -> Maybe JSVal -> Maybe VTTRegionList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> VTTRegionList
VTTRegionList (Maybe JSVal -> Maybe VTTRegionList)
-> JSM (Maybe JSVal) -> JSM (Maybe VTTRegionList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM VTTRegionList
fromJSValUnchecked = VTTRegionList -> JSM VTTRegionList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (VTTRegionList -> JSM VTTRegionList)
-> (JSVal -> VTTRegionList) -> JSVal -> JSM VTTRegionList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> VTTRegionList
VTTRegionList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject VTTRegionList where
  makeObject :: VTTRegionList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (VTTRegionList -> JSVal) -> VTTRegionList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VTTRegionList -> JSVal
unVTTRegionList

instance IsGObject VTTRegionList where
  typeGType :: VTTRegionList -> JSM GType
typeGType VTTRegionList
_ = JSM GType
gTypeVTTRegionList
  {-# INLINE typeGType #-}

noVTTRegionList :: Maybe VTTRegionList
noVTTRegionList :: Maybe VTTRegionList
noVTTRegionList = Maybe VTTRegionList
forall a. Maybe a
Nothing
{-# INLINE noVTTRegionList #-}

gTypeVTTRegionList :: JSM GType
gTypeVTTRegionList :: JSM GType
gTypeVTTRegionList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"VTTRegionList"

-- | Functions for this inteface are in "JSDOM.ValidityState".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/ValidityState Mozilla ValidityState documentation>
newtype ValidityState = ValidityState { ValidityState -> JSVal
unValidityState :: JSVal }

instance PToJSVal ValidityState where
  pToJSVal :: ValidityState -> JSVal
pToJSVal = ValidityState -> JSVal
unValidityState
  {-# INLINE pToJSVal #-}

instance PFromJSVal ValidityState where
  pFromJSVal :: JSVal -> ValidityState
pFromJSVal = JSVal -> ValidityState
ValidityState
  {-# INLINE pFromJSVal #-}

instance ToJSVal ValidityState where
  toJSVal :: ValidityState -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (ValidityState -> JSVal) -> ValidityState -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValidityState -> JSVal
unValidityState
  {-# INLINE toJSVal #-}

instance FromJSVal ValidityState where
  fromJSVal :: JSVal -> JSM (Maybe ValidityState)
fromJSVal JSVal
v = (JSVal -> ValidityState) -> Maybe JSVal -> Maybe ValidityState
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> ValidityState
ValidityState (Maybe JSVal -> Maybe ValidityState)
-> JSM (Maybe JSVal) -> JSM (Maybe ValidityState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM ValidityState
fromJSValUnchecked = ValidityState -> JSM ValidityState
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (ValidityState -> JSM ValidityState)
-> (JSVal -> ValidityState) -> JSVal -> JSM ValidityState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> ValidityState
ValidityState
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject ValidityState where
  makeObject :: ValidityState -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (ValidityState -> JSVal) -> ValidityState -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValidityState -> JSVal
unValidityState

instance IsGObject ValidityState where
  typeGType :: ValidityState -> JSM GType
typeGType ValidityState
_ = JSM GType
gTypeValidityState
  {-# INLINE typeGType #-}

noValidityState :: Maybe ValidityState
noValidityState :: Maybe ValidityState
noValidityState = Maybe ValidityState
forall a. Maybe a
Nothing
{-# INLINE noValidityState #-}

gTypeValidityState :: JSM GType
gTypeValidityState :: JSM GType
gTypeValidityState = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"ValidityState"

-- | Functions for this inteface are in "JSDOM.VideoPlaybackQuality".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/VideoPlaybackQuality Mozilla VideoPlaybackQuality documentation>
newtype VideoPlaybackQuality = VideoPlaybackQuality { VideoPlaybackQuality -> JSVal
unVideoPlaybackQuality :: JSVal }

instance PToJSVal VideoPlaybackQuality where
  pToJSVal :: VideoPlaybackQuality -> JSVal
pToJSVal = VideoPlaybackQuality -> JSVal
unVideoPlaybackQuality
  {-# INLINE pToJSVal #-}

instance PFromJSVal VideoPlaybackQuality where
  pFromJSVal :: JSVal -> VideoPlaybackQuality
pFromJSVal = JSVal -> VideoPlaybackQuality
VideoPlaybackQuality
  {-# INLINE pFromJSVal #-}

instance ToJSVal VideoPlaybackQuality where
  toJSVal :: VideoPlaybackQuality -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (VideoPlaybackQuality -> JSVal)
-> VideoPlaybackQuality
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VideoPlaybackQuality -> JSVal
unVideoPlaybackQuality
  {-# INLINE toJSVal #-}

instance FromJSVal VideoPlaybackQuality where
  fromJSVal :: JSVal -> JSM (Maybe VideoPlaybackQuality)
fromJSVal JSVal
v = (JSVal -> VideoPlaybackQuality)
-> Maybe JSVal -> Maybe VideoPlaybackQuality
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> VideoPlaybackQuality
VideoPlaybackQuality (Maybe JSVal -> Maybe VideoPlaybackQuality)
-> JSM (Maybe JSVal) -> JSM (Maybe VideoPlaybackQuality)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM VideoPlaybackQuality
fromJSValUnchecked = VideoPlaybackQuality -> JSM VideoPlaybackQuality
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (VideoPlaybackQuality -> JSM VideoPlaybackQuality)
-> (JSVal -> VideoPlaybackQuality)
-> JSVal
-> JSM VideoPlaybackQuality
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> VideoPlaybackQuality
VideoPlaybackQuality
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject VideoPlaybackQuality where
  makeObject :: VideoPlaybackQuality -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (VideoPlaybackQuality -> JSVal)
-> VideoPlaybackQuality
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VideoPlaybackQuality -> JSVal
unVideoPlaybackQuality

instance IsGObject VideoPlaybackQuality where
  typeGType :: VideoPlaybackQuality -> JSM GType
typeGType VideoPlaybackQuality
_ = JSM GType
gTypeVideoPlaybackQuality
  {-# INLINE typeGType #-}

noVideoPlaybackQuality :: Maybe VideoPlaybackQuality
noVideoPlaybackQuality :: Maybe VideoPlaybackQuality
noVideoPlaybackQuality = Maybe VideoPlaybackQuality
forall a. Maybe a
Nothing
{-# INLINE noVideoPlaybackQuality #-}

gTypeVideoPlaybackQuality :: JSM GType
gTypeVideoPlaybackQuality :: JSM GType
gTypeVideoPlaybackQuality = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"VideoPlaybackQuality"

-- | Functions for this inteface are in "JSDOM.VideoTrack".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/VideoTrack Mozilla VideoTrack documentation>
newtype VideoTrack = VideoTrack { VideoTrack -> JSVal
unVideoTrack :: JSVal }

instance PToJSVal VideoTrack where
  pToJSVal :: VideoTrack -> JSVal
pToJSVal = VideoTrack -> JSVal
unVideoTrack
  {-# INLINE pToJSVal #-}

instance PFromJSVal VideoTrack where
  pFromJSVal :: JSVal -> VideoTrack
pFromJSVal = JSVal -> VideoTrack
VideoTrack
  {-# INLINE pFromJSVal #-}

instance ToJSVal VideoTrack where
  toJSVal :: VideoTrack -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (VideoTrack -> JSVal) -> VideoTrack -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VideoTrack -> JSVal
unVideoTrack
  {-# INLINE toJSVal #-}

instance FromJSVal VideoTrack where
  fromJSVal :: JSVal -> JSM (Maybe VideoTrack)
fromJSVal JSVal
v = (JSVal -> VideoTrack) -> Maybe JSVal -> Maybe VideoTrack
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> VideoTrack
VideoTrack (Maybe JSVal -> Maybe VideoTrack)
-> JSM (Maybe JSVal) -> JSM (Maybe VideoTrack)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM VideoTrack
fromJSValUnchecked = VideoTrack -> JSM VideoTrack
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (VideoTrack -> JSM VideoTrack)
-> (JSVal -> VideoTrack) -> JSVal -> JSM VideoTrack
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> VideoTrack
VideoTrack
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject VideoTrack where
  makeObject :: VideoTrack -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (VideoTrack -> JSVal) -> VideoTrack -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VideoTrack -> JSVal
unVideoTrack

instance IsGObject VideoTrack where
  typeGType :: VideoTrack -> JSM GType
typeGType VideoTrack
_ = JSM GType
gTypeVideoTrack
  {-# INLINE typeGType #-}

noVideoTrack :: Maybe VideoTrack
noVideoTrack :: Maybe VideoTrack
noVideoTrack = Maybe VideoTrack
forall a. Maybe a
Nothing
{-# INLINE noVideoTrack #-}

gTypeVideoTrack :: JSM GType
gTypeVideoTrack :: JSM GType
gTypeVideoTrack = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"VideoTrack"

-- | Functions for this inteface are in "JSDOM.VideoTrackList".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/VideoTrackList Mozilla VideoTrackList documentation>
newtype VideoTrackList = VideoTrackList { VideoTrackList -> JSVal
unVideoTrackList :: JSVal }

instance PToJSVal VideoTrackList where
  pToJSVal :: VideoTrackList -> JSVal
pToJSVal = VideoTrackList -> JSVal
unVideoTrackList
  {-# INLINE pToJSVal #-}

instance PFromJSVal VideoTrackList where
  pFromJSVal :: JSVal -> VideoTrackList
pFromJSVal = JSVal -> VideoTrackList
VideoTrackList
  {-# INLINE pFromJSVal #-}

instance ToJSVal VideoTrackList where
  toJSVal :: VideoTrackList -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (VideoTrackList -> JSVal) -> VideoTrackList -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VideoTrackList -> JSVal
unVideoTrackList
  {-# INLINE toJSVal #-}

instance FromJSVal VideoTrackList where
  fromJSVal :: JSVal -> JSM (Maybe VideoTrackList)
fromJSVal JSVal
v = (JSVal -> VideoTrackList) -> Maybe JSVal -> Maybe VideoTrackList
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> VideoTrackList
VideoTrackList (Maybe JSVal -> Maybe VideoTrackList)
-> JSM (Maybe JSVal) -> JSM (Maybe VideoTrackList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM VideoTrackList
fromJSValUnchecked = VideoTrackList -> JSM VideoTrackList
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (VideoTrackList -> JSM VideoTrackList)
-> (JSVal -> VideoTrackList) -> JSVal -> JSM VideoTrackList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> VideoTrackList
VideoTrackList
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject VideoTrackList where
  makeObject :: VideoTrackList -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (VideoTrackList -> JSVal) -> VideoTrackList -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VideoTrackList -> JSVal
unVideoTrackList

instance IsEventTarget VideoTrackList
instance IsGObject VideoTrackList where
  typeGType :: VideoTrackList -> JSM GType
typeGType VideoTrackList
_ = JSM GType
gTypeVideoTrackList
  {-# INLINE typeGType #-}

noVideoTrackList :: Maybe VideoTrackList
noVideoTrackList :: Maybe VideoTrackList
noVideoTrackList = Maybe VideoTrackList
forall a. Maybe a
Nothing
{-# INLINE noVideoTrackList #-}

gTypeVideoTrackList :: JSM GType
gTypeVideoTrackList :: JSM GType
gTypeVideoTrackList = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"VideoTrackList"

-- | Functions for this inteface are in "JSDOM.WaveShaperNode".
-- Base interface functions are in:
--
--     * "JSDOM.AudioNode"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WaveShaperNode Mozilla WaveShaperNode documentation>
newtype WaveShaperNode = WaveShaperNode { WaveShaperNode -> JSVal
unWaveShaperNode :: JSVal }

instance PToJSVal WaveShaperNode where
  pToJSVal :: WaveShaperNode -> JSVal
pToJSVal = WaveShaperNode -> JSVal
unWaveShaperNode
  {-# INLINE pToJSVal #-}

instance PFromJSVal WaveShaperNode where
  pFromJSVal :: JSVal -> WaveShaperNode
pFromJSVal = JSVal -> WaveShaperNode
WaveShaperNode
  {-# INLINE pFromJSVal #-}

instance ToJSVal WaveShaperNode where
  toJSVal :: WaveShaperNode -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WaveShaperNode -> JSVal) -> WaveShaperNode -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WaveShaperNode -> JSVal
unWaveShaperNode
  {-# INLINE toJSVal #-}

instance FromJSVal WaveShaperNode where
  fromJSVal :: JSVal -> JSM (Maybe WaveShaperNode)
fromJSVal JSVal
v = (JSVal -> WaveShaperNode) -> Maybe JSVal -> Maybe WaveShaperNode
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WaveShaperNode
WaveShaperNode (Maybe JSVal -> Maybe WaveShaperNode)
-> JSM (Maybe JSVal) -> JSM (Maybe WaveShaperNode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WaveShaperNode
fromJSValUnchecked = WaveShaperNode -> JSM WaveShaperNode
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WaveShaperNode -> JSM WaveShaperNode)
-> (JSVal -> WaveShaperNode) -> JSVal -> JSM WaveShaperNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WaveShaperNode
WaveShaperNode
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WaveShaperNode where
  makeObject :: WaveShaperNode -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WaveShaperNode -> JSVal) -> WaveShaperNode -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WaveShaperNode -> JSVal
unWaveShaperNode

instance IsAudioNode WaveShaperNode
instance IsEventTarget WaveShaperNode
instance IsGObject WaveShaperNode where
  typeGType :: WaveShaperNode -> JSM GType
typeGType WaveShaperNode
_ = JSM GType
gTypeWaveShaperNode
  {-# INLINE typeGType #-}

noWaveShaperNode :: Maybe WaveShaperNode
noWaveShaperNode :: Maybe WaveShaperNode
noWaveShaperNode = Maybe WaveShaperNode
forall a. Maybe a
Nothing
{-# INLINE noWaveShaperNode #-}

gTypeWaveShaperNode :: JSM GType
gTypeWaveShaperNode :: JSM GType
gTypeWaveShaperNode = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WaveShaperNode"

-- | Functions for this inteface are in "JSDOM.WebGL2RenderingContext".
-- Base interface functions are in:
--
--     * "JSDOM.WebGLRenderingContextBase"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGL2RenderingContext Mozilla WebGL2RenderingContext documentation>
newtype WebGL2RenderingContext = WebGL2RenderingContext { WebGL2RenderingContext -> JSVal
unWebGL2RenderingContext :: JSVal }

instance PToJSVal WebGL2RenderingContext where
  pToJSVal :: WebGL2RenderingContext -> JSVal
pToJSVal = WebGL2RenderingContext -> JSVal
unWebGL2RenderingContext
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGL2RenderingContext where
  pFromJSVal :: JSVal -> WebGL2RenderingContext
pFromJSVal = JSVal -> WebGL2RenderingContext
WebGL2RenderingContext
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGL2RenderingContext where
  toJSVal :: WebGL2RenderingContext -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGL2RenderingContext -> JSVal)
-> WebGL2RenderingContext
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGL2RenderingContext -> JSVal
unWebGL2RenderingContext
  {-# INLINE toJSVal #-}

instance FromJSVal WebGL2RenderingContext where
  fromJSVal :: JSVal -> JSM (Maybe WebGL2RenderingContext)
fromJSVal JSVal
v = (JSVal -> WebGL2RenderingContext)
-> Maybe JSVal -> Maybe WebGL2RenderingContext
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGL2RenderingContext
WebGL2RenderingContext (Maybe JSVal -> Maybe WebGL2RenderingContext)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGL2RenderingContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGL2RenderingContext
fromJSValUnchecked = WebGL2RenderingContext -> JSM WebGL2RenderingContext
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGL2RenderingContext -> JSM WebGL2RenderingContext)
-> (JSVal -> WebGL2RenderingContext)
-> JSVal
-> JSM WebGL2RenderingContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGL2RenderingContext
WebGL2RenderingContext
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGL2RenderingContext where
  makeObject :: WebGL2RenderingContext -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGL2RenderingContext -> JSVal)
-> WebGL2RenderingContext
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGL2RenderingContext -> JSVal
unWebGL2RenderingContext

instance IsWebGLRenderingContextBase WebGL2RenderingContext
instance IsGObject WebGL2RenderingContext where
  typeGType :: WebGL2RenderingContext -> JSM GType
typeGType WebGL2RenderingContext
_ = JSM GType
gTypeWebGL2RenderingContext
  {-# INLINE typeGType #-}

noWebGL2RenderingContext :: Maybe WebGL2RenderingContext
noWebGL2RenderingContext :: Maybe WebGL2RenderingContext
noWebGL2RenderingContext = Maybe WebGL2RenderingContext
forall a. Maybe a
Nothing
{-# INLINE noWebGL2RenderingContext #-}

gTypeWebGL2RenderingContext :: JSM GType
gTypeWebGL2RenderingContext :: JSM GType
gTypeWebGL2RenderingContext = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGL2RenderingContext"

-- | Functions for this inteface are in "JSDOM.WebGLActiveInfo".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLActiveInfo Mozilla WebGLActiveInfo documentation>
newtype WebGLActiveInfo = WebGLActiveInfo { WebGLActiveInfo -> JSVal
unWebGLActiveInfo :: JSVal }

instance PToJSVal WebGLActiveInfo where
  pToJSVal :: WebGLActiveInfo -> JSVal
pToJSVal = WebGLActiveInfo -> JSVal
unWebGLActiveInfo
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLActiveInfo where
  pFromJSVal :: JSVal -> WebGLActiveInfo
pFromJSVal = JSVal -> WebGLActiveInfo
WebGLActiveInfo
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLActiveInfo where
  toJSVal :: WebGLActiveInfo -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLActiveInfo -> JSVal) -> WebGLActiveInfo -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLActiveInfo -> JSVal
unWebGLActiveInfo
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLActiveInfo where
  fromJSVal :: JSVal -> JSM (Maybe WebGLActiveInfo)
fromJSVal JSVal
v = (JSVal -> WebGLActiveInfo) -> Maybe JSVal -> Maybe WebGLActiveInfo
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLActiveInfo
WebGLActiveInfo (Maybe JSVal -> Maybe WebGLActiveInfo)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLActiveInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLActiveInfo
fromJSValUnchecked = WebGLActiveInfo -> JSM WebGLActiveInfo
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLActiveInfo -> JSM WebGLActiveInfo)
-> (JSVal -> WebGLActiveInfo) -> JSVal -> JSM WebGLActiveInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLActiveInfo
WebGLActiveInfo
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLActiveInfo where
  makeObject :: WebGLActiveInfo -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLActiveInfo -> JSVal) -> WebGLActiveInfo -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLActiveInfo -> JSVal
unWebGLActiveInfo

instance IsGObject WebGLActiveInfo where
  typeGType :: WebGLActiveInfo -> JSM GType
typeGType WebGLActiveInfo
_ = JSM GType
gTypeWebGLActiveInfo
  {-# INLINE typeGType #-}

noWebGLActiveInfo :: Maybe WebGLActiveInfo
noWebGLActiveInfo :: Maybe WebGLActiveInfo
noWebGLActiveInfo = Maybe WebGLActiveInfo
forall a. Maybe a
Nothing
{-# INLINE noWebGLActiveInfo #-}

gTypeWebGLActiveInfo :: JSM GType
gTypeWebGLActiveInfo :: JSM GType
gTypeWebGLActiveInfo = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLActiveInfo"

-- | Functions for this inteface are in "JSDOM.WebGLBuffer".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLBuffer Mozilla WebGLBuffer documentation>
newtype WebGLBuffer = WebGLBuffer { WebGLBuffer -> JSVal
unWebGLBuffer :: JSVal }

instance PToJSVal WebGLBuffer where
  pToJSVal :: WebGLBuffer -> JSVal
pToJSVal = WebGLBuffer -> JSVal
unWebGLBuffer
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLBuffer where
  pFromJSVal :: JSVal -> WebGLBuffer
pFromJSVal = JSVal -> WebGLBuffer
WebGLBuffer
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLBuffer where
  toJSVal :: WebGLBuffer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLBuffer -> JSVal) -> WebGLBuffer -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLBuffer -> JSVal
unWebGLBuffer
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLBuffer where
  fromJSVal :: JSVal -> JSM (Maybe WebGLBuffer)
fromJSVal JSVal
v = (JSVal -> WebGLBuffer) -> Maybe JSVal -> Maybe WebGLBuffer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLBuffer
WebGLBuffer (Maybe JSVal -> Maybe WebGLBuffer)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLBuffer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLBuffer
fromJSValUnchecked = WebGLBuffer -> JSM WebGLBuffer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLBuffer -> JSM WebGLBuffer)
-> (JSVal -> WebGLBuffer) -> JSVal -> JSM WebGLBuffer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLBuffer
WebGLBuffer
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLBuffer where
  makeObject :: WebGLBuffer -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLBuffer -> JSVal) -> WebGLBuffer -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLBuffer -> JSVal
unWebGLBuffer

instance IsGObject WebGLBuffer where
  typeGType :: WebGLBuffer -> JSM GType
typeGType WebGLBuffer
_ = JSM GType
gTypeWebGLBuffer
  {-# INLINE typeGType #-}

noWebGLBuffer :: Maybe WebGLBuffer
noWebGLBuffer :: Maybe WebGLBuffer
noWebGLBuffer = Maybe WebGLBuffer
forall a. Maybe a
Nothing
{-# INLINE noWebGLBuffer #-}

gTypeWebGLBuffer :: JSM GType
gTypeWebGLBuffer :: JSM GType
gTypeWebGLBuffer = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLBuffer"

-- | Functions for this inteface are in "JSDOM.WebGLCompressedTextureATC".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLCompressedTextureATC Mozilla WebGLCompressedTextureATC documentation>
newtype WebGLCompressedTextureATC = WebGLCompressedTextureATC { WebGLCompressedTextureATC -> JSVal
unWebGLCompressedTextureATC :: JSVal }

instance PToJSVal WebGLCompressedTextureATC where
  pToJSVal :: WebGLCompressedTextureATC -> JSVal
pToJSVal = WebGLCompressedTextureATC -> JSVal
unWebGLCompressedTextureATC
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLCompressedTextureATC where
  pFromJSVal :: JSVal -> WebGLCompressedTextureATC
pFromJSVal = JSVal -> WebGLCompressedTextureATC
WebGLCompressedTextureATC
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLCompressedTextureATC where
  toJSVal :: WebGLCompressedTextureATC -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLCompressedTextureATC -> JSVal)
-> WebGLCompressedTextureATC
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLCompressedTextureATC -> JSVal
unWebGLCompressedTextureATC
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLCompressedTextureATC where
  fromJSVal :: JSVal -> JSM (Maybe WebGLCompressedTextureATC)
fromJSVal JSVal
v = (JSVal -> WebGLCompressedTextureATC)
-> Maybe JSVal -> Maybe WebGLCompressedTextureATC
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLCompressedTextureATC
WebGLCompressedTextureATC (Maybe JSVal -> Maybe WebGLCompressedTextureATC)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLCompressedTextureATC)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLCompressedTextureATC
fromJSValUnchecked = WebGLCompressedTextureATC -> JSM WebGLCompressedTextureATC
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLCompressedTextureATC -> JSM WebGLCompressedTextureATC)
-> (JSVal -> WebGLCompressedTextureATC)
-> JSVal
-> JSM WebGLCompressedTextureATC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLCompressedTextureATC
WebGLCompressedTextureATC
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLCompressedTextureATC where
  makeObject :: WebGLCompressedTextureATC -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLCompressedTextureATC -> JSVal)
-> WebGLCompressedTextureATC
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLCompressedTextureATC -> JSVal
unWebGLCompressedTextureATC

instance IsGObject WebGLCompressedTextureATC where
  typeGType :: WebGLCompressedTextureATC -> JSM GType
typeGType WebGLCompressedTextureATC
_ = JSM GType
gTypeWebGLCompressedTextureATC
  {-# INLINE typeGType #-}

noWebGLCompressedTextureATC :: Maybe WebGLCompressedTextureATC
noWebGLCompressedTextureATC :: Maybe WebGLCompressedTextureATC
noWebGLCompressedTextureATC = Maybe WebGLCompressedTextureATC
forall a. Maybe a
Nothing
{-# INLINE noWebGLCompressedTextureATC #-}

gTypeWebGLCompressedTextureATC :: JSM GType
gTypeWebGLCompressedTextureATC :: JSM GType
gTypeWebGLCompressedTextureATC = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLCompressedTextureATC"

-- | Functions for this inteface are in "JSDOM.WebGLCompressedTexturePVRTC".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLCompressedTexturePVRTC Mozilla WebGLCompressedTexturePVRTC documentation>
newtype WebGLCompressedTexturePVRTC = WebGLCompressedTexturePVRTC { WebGLCompressedTexturePVRTC -> JSVal
unWebGLCompressedTexturePVRTC :: JSVal }

instance PToJSVal WebGLCompressedTexturePVRTC where
  pToJSVal :: WebGLCompressedTexturePVRTC -> JSVal
pToJSVal = WebGLCompressedTexturePVRTC -> JSVal
unWebGLCompressedTexturePVRTC
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLCompressedTexturePVRTC where
  pFromJSVal :: JSVal -> WebGLCompressedTexturePVRTC
pFromJSVal = JSVal -> WebGLCompressedTexturePVRTC
WebGLCompressedTexturePVRTC
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLCompressedTexturePVRTC where
  toJSVal :: WebGLCompressedTexturePVRTC -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLCompressedTexturePVRTC -> JSVal)
-> WebGLCompressedTexturePVRTC
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLCompressedTexturePVRTC -> JSVal
unWebGLCompressedTexturePVRTC
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLCompressedTexturePVRTC where
  fromJSVal :: JSVal -> JSM (Maybe WebGLCompressedTexturePVRTC)
fromJSVal JSVal
v = (JSVal -> WebGLCompressedTexturePVRTC)
-> Maybe JSVal -> Maybe WebGLCompressedTexturePVRTC
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLCompressedTexturePVRTC
WebGLCompressedTexturePVRTC (Maybe JSVal -> Maybe WebGLCompressedTexturePVRTC)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLCompressedTexturePVRTC)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLCompressedTexturePVRTC
fromJSValUnchecked = WebGLCompressedTexturePVRTC -> JSM WebGLCompressedTexturePVRTC
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLCompressedTexturePVRTC -> JSM WebGLCompressedTexturePVRTC)
-> (JSVal -> WebGLCompressedTexturePVRTC)
-> JSVal
-> JSM WebGLCompressedTexturePVRTC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLCompressedTexturePVRTC
WebGLCompressedTexturePVRTC
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLCompressedTexturePVRTC where
  makeObject :: WebGLCompressedTexturePVRTC -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLCompressedTexturePVRTC -> JSVal)
-> WebGLCompressedTexturePVRTC
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLCompressedTexturePVRTC -> JSVal
unWebGLCompressedTexturePVRTC

instance IsGObject WebGLCompressedTexturePVRTC where
  typeGType :: WebGLCompressedTexturePVRTC -> JSM GType
typeGType WebGLCompressedTexturePVRTC
_ = JSM GType
gTypeWebGLCompressedTexturePVRTC
  {-# INLINE typeGType #-}

noWebGLCompressedTexturePVRTC :: Maybe WebGLCompressedTexturePVRTC
noWebGLCompressedTexturePVRTC :: Maybe WebGLCompressedTexturePVRTC
noWebGLCompressedTexturePVRTC = Maybe WebGLCompressedTexturePVRTC
forall a. Maybe a
Nothing
{-# INLINE noWebGLCompressedTexturePVRTC #-}

gTypeWebGLCompressedTexturePVRTC :: JSM GType
gTypeWebGLCompressedTexturePVRTC :: JSM GType
gTypeWebGLCompressedTexturePVRTC = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLCompressedTexturePVRTC"

-- | Functions for this inteface are in "JSDOM.WebGLCompressedTextureS3TC".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLCompressedTextureS3TC Mozilla WebGLCompressedTextureS3TC documentation>
newtype WebGLCompressedTextureS3TC = WebGLCompressedTextureS3TC { WebGLCompressedTextureS3TC -> JSVal
unWebGLCompressedTextureS3TC :: JSVal }

instance PToJSVal WebGLCompressedTextureS3TC where
  pToJSVal :: WebGLCompressedTextureS3TC -> JSVal
pToJSVal = WebGLCompressedTextureS3TC -> JSVal
unWebGLCompressedTextureS3TC
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLCompressedTextureS3TC where
  pFromJSVal :: JSVal -> WebGLCompressedTextureS3TC
pFromJSVal = JSVal -> WebGLCompressedTextureS3TC
WebGLCompressedTextureS3TC
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLCompressedTextureS3TC where
  toJSVal :: WebGLCompressedTextureS3TC -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLCompressedTextureS3TC -> JSVal)
-> WebGLCompressedTextureS3TC
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLCompressedTextureS3TC -> JSVal
unWebGLCompressedTextureS3TC
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLCompressedTextureS3TC where
  fromJSVal :: JSVal -> JSM (Maybe WebGLCompressedTextureS3TC)
fromJSVal JSVal
v = (JSVal -> WebGLCompressedTextureS3TC)
-> Maybe JSVal -> Maybe WebGLCompressedTextureS3TC
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLCompressedTextureS3TC
WebGLCompressedTextureS3TC (Maybe JSVal -> Maybe WebGLCompressedTextureS3TC)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLCompressedTextureS3TC)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLCompressedTextureS3TC
fromJSValUnchecked = WebGLCompressedTextureS3TC -> JSM WebGLCompressedTextureS3TC
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLCompressedTextureS3TC -> JSM WebGLCompressedTextureS3TC)
-> (JSVal -> WebGLCompressedTextureS3TC)
-> JSVal
-> JSM WebGLCompressedTextureS3TC
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLCompressedTextureS3TC
WebGLCompressedTextureS3TC
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLCompressedTextureS3TC where
  makeObject :: WebGLCompressedTextureS3TC -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLCompressedTextureS3TC -> JSVal)
-> WebGLCompressedTextureS3TC
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLCompressedTextureS3TC -> JSVal
unWebGLCompressedTextureS3TC

instance IsGObject WebGLCompressedTextureS3TC where
  typeGType :: WebGLCompressedTextureS3TC -> JSM GType
typeGType WebGLCompressedTextureS3TC
_ = JSM GType
gTypeWebGLCompressedTextureS3TC
  {-# INLINE typeGType #-}

noWebGLCompressedTextureS3TC :: Maybe WebGLCompressedTextureS3TC
noWebGLCompressedTextureS3TC :: Maybe WebGLCompressedTextureS3TC
noWebGLCompressedTextureS3TC = Maybe WebGLCompressedTextureS3TC
forall a. Maybe a
Nothing
{-# INLINE noWebGLCompressedTextureS3TC #-}

gTypeWebGLCompressedTextureS3TC :: JSM GType
gTypeWebGLCompressedTextureS3TC :: JSM GType
gTypeWebGLCompressedTextureS3TC = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLCompressedTextureS3TC"

-- | Functions for this inteface are in "JSDOM.WebGLContextAttributes".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLContextAttributes Mozilla WebGLContextAttributes documentation>
newtype WebGLContextAttributes = WebGLContextAttributes { WebGLContextAttributes -> JSVal
unWebGLContextAttributes :: JSVal }

instance PToJSVal WebGLContextAttributes where
  pToJSVal :: WebGLContextAttributes -> JSVal
pToJSVal = WebGLContextAttributes -> JSVal
unWebGLContextAttributes
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLContextAttributes where
  pFromJSVal :: JSVal -> WebGLContextAttributes
pFromJSVal = JSVal -> WebGLContextAttributes
WebGLContextAttributes
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLContextAttributes where
  toJSVal :: WebGLContextAttributes -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLContextAttributes -> JSVal)
-> WebGLContextAttributes
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLContextAttributes -> JSVal
unWebGLContextAttributes
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLContextAttributes where
  fromJSVal :: JSVal -> JSM (Maybe WebGLContextAttributes)
fromJSVal JSVal
v = (JSVal -> WebGLContextAttributes)
-> Maybe JSVal -> Maybe WebGLContextAttributes
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLContextAttributes
WebGLContextAttributes (Maybe JSVal -> Maybe WebGLContextAttributes)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLContextAttributes)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLContextAttributes
fromJSValUnchecked = WebGLContextAttributes -> JSM WebGLContextAttributes
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLContextAttributes -> JSM WebGLContextAttributes)
-> (JSVal -> WebGLContextAttributes)
-> JSVal
-> JSM WebGLContextAttributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLContextAttributes
WebGLContextAttributes
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLContextAttributes where
  makeObject :: WebGLContextAttributes -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLContextAttributes -> JSVal)
-> WebGLContextAttributes
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLContextAttributes -> JSVal
unWebGLContextAttributes

instance IsGObject WebGLContextAttributes where
  typeGType :: WebGLContextAttributes -> JSM GType
typeGType WebGLContextAttributes
_ = JSM GType
gTypeWebGLContextAttributes
  {-# INLINE typeGType #-}

noWebGLContextAttributes :: Maybe WebGLContextAttributes
noWebGLContextAttributes :: Maybe WebGLContextAttributes
noWebGLContextAttributes = Maybe WebGLContextAttributes
forall a. Maybe a
Nothing
{-# INLINE noWebGLContextAttributes #-}

gTypeWebGLContextAttributes :: JSM GType
gTypeWebGLContextAttributes :: JSM GType
gTypeWebGLContextAttributes = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLContextAttributes"

-- | Functions for this inteface are in "JSDOM.WebGLContextEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLContextEvent Mozilla WebGLContextEvent documentation>
newtype WebGLContextEvent = WebGLContextEvent { WebGLContextEvent -> JSVal
unWebGLContextEvent :: JSVal }

instance PToJSVal WebGLContextEvent where
  pToJSVal :: WebGLContextEvent -> JSVal
pToJSVal = WebGLContextEvent -> JSVal
unWebGLContextEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLContextEvent where
  pFromJSVal :: JSVal -> WebGLContextEvent
pFromJSVal = JSVal -> WebGLContextEvent
WebGLContextEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLContextEvent where
  toJSVal :: WebGLContextEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLContextEvent -> JSVal) -> WebGLContextEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLContextEvent -> JSVal
unWebGLContextEvent
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLContextEvent where
  fromJSVal :: JSVal -> JSM (Maybe WebGLContextEvent)
fromJSVal JSVal
v = (JSVal -> WebGLContextEvent)
-> Maybe JSVal -> Maybe WebGLContextEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLContextEvent
WebGLContextEvent (Maybe JSVal -> Maybe WebGLContextEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLContextEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLContextEvent
fromJSValUnchecked = WebGLContextEvent -> JSM WebGLContextEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLContextEvent -> JSM WebGLContextEvent)
-> (JSVal -> WebGLContextEvent) -> JSVal -> JSM WebGLContextEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLContextEvent
WebGLContextEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLContextEvent where
  makeObject :: WebGLContextEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLContextEvent -> JSVal) -> WebGLContextEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLContextEvent -> JSVal
unWebGLContextEvent

instance IsEvent WebGLContextEvent
instance IsGObject WebGLContextEvent where
  typeGType :: WebGLContextEvent -> JSM GType
typeGType WebGLContextEvent
_ = JSM GType
gTypeWebGLContextEvent
  {-# INLINE typeGType #-}

noWebGLContextEvent :: Maybe WebGLContextEvent
noWebGLContextEvent :: Maybe WebGLContextEvent
noWebGLContextEvent = Maybe WebGLContextEvent
forall a. Maybe a
Nothing
{-# INLINE noWebGLContextEvent #-}

gTypeWebGLContextEvent :: JSM GType
gTypeWebGLContextEvent :: JSM GType
gTypeWebGLContextEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLContextEvent"

-- | Functions for this inteface are in "JSDOM.WebGLContextEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLContextEventInit Mozilla WebGLContextEventInit documentation>
newtype WebGLContextEventInit = WebGLContextEventInit { WebGLContextEventInit -> JSVal
unWebGLContextEventInit :: JSVal }

instance PToJSVal WebGLContextEventInit where
  pToJSVal :: WebGLContextEventInit -> JSVal
pToJSVal = WebGLContextEventInit -> JSVal
unWebGLContextEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLContextEventInit where
  pFromJSVal :: JSVal -> WebGLContextEventInit
pFromJSVal = JSVal -> WebGLContextEventInit
WebGLContextEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLContextEventInit where
  toJSVal :: WebGLContextEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLContextEventInit -> JSVal)
-> WebGLContextEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLContextEventInit -> JSVal
unWebGLContextEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLContextEventInit where
  fromJSVal :: JSVal -> JSM (Maybe WebGLContextEventInit)
fromJSVal JSVal
v = (JSVal -> WebGLContextEventInit)
-> Maybe JSVal -> Maybe WebGLContextEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLContextEventInit
WebGLContextEventInit (Maybe JSVal -> Maybe WebGLContextEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLContextEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLContextEventInit
fromJSValUnchecked = WebGLContextEventInit -> JSM WebGLContextEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLContextEventInit -> JSM WebGLContextEventInit)
-> (JSVal -> WebGLContextEventInit)
-> JSVal
-> JSM WebGLContextEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLContextEventInit
WebGLContextEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLContextEventInit where
  makeObject :: WebGLContextEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLContextEventInit -> JSVal)
-> WebGLContextEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLContextEventInit -> JSVal
unWebGLContextEventInit

instance IsEventInit WebGLContextEventInit
instance IsGObject WebGLContextEventInit where
  typeGType :: WebGLContextEventInit -> JSM GType
typeGType WebGLContextEventInit
_ = JSM GType
gTypeWebGLContextEventInit
  {-# INLINE typeGType #-}

noWebGLContextEventInit :: Maybe WebGLContextEventInit
noWebGLContextEventInit :: Maybe WebGLContextEventInit
noWebGLContextEventInit = Maybe WebGLContextEventInit
forall a. Maybe a
Nothing
{-# INLINE noWebGLContextEventInit #-}

gTypeWebGLContextEventInit :: JSM GType
gTypeWebGLContextEventInit :: JSM GType
gTypeWebGLContextEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLContextEventInit"

-- | Functions for this inteface are in "JSDOM.WebGLDebugRendererInfo".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLDebugRendererInfo Mozilla WebGLDebugRendererInfo documentation>
newtype WebGLDebugRendererInfo = WebGLDebugRendererInfo { WebGLDebugRendererInfo -> JSVal
unWebGLDebugRendererInfo :: JSVal }

instance PToJSVal WebGLDebugRendererInfo where
  pToJSVal :: WebGLDebugRendererInfo -> JSVal
pToJSVal = WebGLDebugRendererInfo -> JSVal
unWebGLDebugRendererInfo
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLDebugRendererInfo where
  pFromJSVal :: JSVal -> WebGLDebugRendererInfo
pFromJSVal = JSVal -> WebGLDebugRendererInfo
WebGLDebugRendererInfo
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLDebugRendererInfo where
  toJSVal :: WebGLDebugRendererInfo -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLDebugRendererInfo -> JSVal)
-> WebGLDebugRendererInfo
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLDebugRendererInfo -> JSVal
unWebGLDebugRendererInfo
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLDebugRendererInfo where
  fromJSVal :: JSVal -> JSM (Maybe WebGLDebugRendererInfo)
fromJSVal JSVal
v = (JSVal -> WebGLDebugRendererInfo)
-> Maybe JSVal -> Maybe WebGLDebugRendererInfo
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLDebugRendererInfo
WebGLDebugRendererInfo (Maybe JSVal -> Maybe WebGLDebugRendererInfo)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLDebugRendererInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLDebugRendererInfo
fromJSValUnchecked = WebGLDebugRendererInfo -> JSM WebGLDebugRendererInfo
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLDebugRendererInfo -> JSM WebGLDebugRendererInfo)
-> (JSVal -> WebGLDebugRendererInfo)
-> JSVal
-> JSM WebGLDebugRendererInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLDebugRendererInfo
WebGLDebugRendererInfo
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLDebugRendererInfo where
  makeObject :: WebGLDebugRendererInfo -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLDebugRendererInfo -> JSVal)
-> WebGLDebugRendererInfo
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLDebugRendererInfo -> JSVal
unWebGLDebugRendererInfo

instance IsGObject WebGLDebugRendererInfo where
  typeGType :: WebGLDebugRendererInfo -> JSM GType
typeGType WebGLDebugRendererInfo
_ = JSM GType
gTypeWebGLDebugRendererInfo
  {-# INLINE typeGType #-}

noWebGLDebugRendererInfo :: Maybe WebGLDebugRendererInfo
noWebGLDebugRendererInfo :: Maybe WebGLDebugRendererInfo
noWebGLDebugRendererInfo = Maybe WebGLDebugRendererInfo
forall a. Maybe a
Nothing
{-# INLINE noWebGLDebugRendererInfo #-}

gTypeWebGLDebugRendererInfo :: JSM GType
gTypeWebGLDebugRendererInfo :: JSM GType
gTypeWebGLDebugRendererInfo = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLDebugRendererInfo"

-- | Functions for this inteface are in "JSDOM.WebGLDebugShaders".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLDebugShaders Mozilla WebGLDebugShaders documentation>
newtype WebGLDebugShaders = WebGLDebugShaders { WebGLDebugShaders -> JSVal
unWebGLDebugShaders :: JSVal }

instance PToJSVal WebGLDebugShaders where
  pToJSVal :: WebGLDebugShaders -> JSVal
pToJSVal = WebGLDebugShaders -> JSVal
unWebGLDebugShaders
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLDebugShaders where
  pFromJSVal :: JSVal -> WebGLDebugShaders
pFromJSVal = JSVal -> WebGLDebugShaders
WebGLDebugShaders
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLDebugShaders where
  toJSVal :: WebGLDebugShaders -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLDebugShaders -> JSVal) -> WebGLDebugShaders -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLDebugShaders -> JSVal
unWebGLDebugShaders
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLDebugShaders where
  fromJSVal :: JSVal -> JSM (Maybe WebGLDebugShaders)
fromJSVal JSVal
v = (JSVal -> WebGLDebugShaders)
-> Maybe JSVal -> Maybe WebGLDebugShaders
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLDebugShaders
WebGLDebugShaders (Maybe JSVal -> Maybe WebGLDebugShaders)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLDebugShaders)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLDebugShaders
fromJSValUnchecked = WebGLDebugShaders -> JSM WebGLDebugShaders
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLDebugShaders -> JSM WebGLDebugShaders)
-> (JSVal -> WebGLDebugShaders) -> JSVal -> JSM WebGLDebugShaders
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLDebugShaders
WebGLDebugShaders
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLDebugShaders where
  makeObject :: WebGLDebugShaders -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLDebugShaders -> JSVal) -> WebGLDebugShaders -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLDebugShaders -> JSVal
unWebGLDebugShaders

instance IsGObject WebGLDebugShaders where
  typeGType :: WebGLDebugShaders -> JSM GType
typeGType WebGLDebugShaders
_ = JSM GType
gTypeWebGLDebugShaders
  {-# INLINE typeGType #-}

noWebGLDebugShaders :: Maybe WebGLDebugShaders
noWebGLDebugShaders :: Maybe WebGLDebugShaders
noWebGLDebugShaders = Maybe WebGLDebugShaders
forall a. Maybe a
Nothing
{-# INLINE noWebGLDebugShaders #-}

gTypeWebGLDebugShaders :: JSM GType
gTypeWebGLDebugShaders :: JSM GType
gTypeWebGLDebugShaders = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLDebugShaders"

-- | Functions for this inteface are in "JSDOM.WebGLDepthTexture".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLDepthTexture Mozilla WebGLDepthTexture documentation>
newtype WebGLDepthTexture = WebGLDepthTexture { WebGLDepthTexture -> JSVal
unWebGLDepthTexture :: JSVal }

instance PToJSVal WebGLDepthTexture where
  pToJSVal :: WebGLDepthTexture -> JSVal
pToJSVal = WebGLDepthTexture -> JSVal
unWebGLDepthTexture
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLDepthTexture where
  pFromJSVal :: JSVal -> WebGLDepthTexture
pFromJSVal = JSVal -> WebGLDepthTexture
WebGLDepthTexture
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLDepthTexture where
  toJSVal :: WebGLDepthTexture -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLDepthTexture -> JSVal) -> WebGLDepthTexture -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLDepthTexture -> JSVal
unWebGLDepthTexture
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLDepthTexture where
  fromJSVal :: JSVal -> JSM (Maybe WebGLDepthTexture)
fromJSVal JSVal
v = (JSVal -> WebGLDepthTexture)
-> Maybe JSVal -> Maybe WebGLDepthTexture
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLDepthTexture
WebGLDepthTexture (Maybe JSVal -> Maybe WebGLDepthTexture)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLDepthTexture)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLDepthTexture
fromJSValUnchecked = WebGLDepthTexture -> JSM WebGLDepthTexture
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLDepthTexture -> JSM WebGLDepthTexture)
-> (JSVal -> WebGLDepthTexture) -> JSVal -> JSM WebGLDepthTexture
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLDepthTexture
WebGLDepthTexture
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLDepthTexture where
  makeObject :: WebGLDepthTexture -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLDepthTexture -> JSVal) -> WebGLDepthTexture -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLDepthTexture -> JSVal
unWebGLDepthTexture

instance IsGObject WebGLDepthTexture where
  typeGType :: WebGLDepthTexture -> JSM GType
typeGType WebGLDepthTexture
_ = JSM GType
gTypeWebGLDepthTexture
  {-# INLINE typeGType #-}

noWebGLDepthTexture :: Maybe WebGLDepthTexture
noWebGLDepthTexture :: Maybe WebGLDepthTexture
noWebGLDepthTexture = Maybe WebGLDepthTexture
forall a. Maybe a
Nothing
{-# INLINE noWebGLDepthTexture #-}

gTypeWebGLDepthTexture :: JSM GType
gTypeWebGLDepthTexture :: JSM GType
gTypeWebGLDepthTexture = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLDepthTexture"

-- | Functions for this inteface are in "JSDOM.WebGLDrawBuffers".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLDrawBuffers Mozilla WebGLDrawBuffers documentation>
newtype WebGLDrawBuffers = WebGLDrawBuffers { WebGLDrawBuffers -> JSVal
unWebGLDrawBuffers :: JSVal }

instance PToJSVal WebGLDrawBuffers where
  pToJSVal :: WebGLDrawBuffers -> JSVal
pToJSVal = WebGLDrawBuffers -> JSVal
unWebGLDrawBuffers
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLDrawBuffers where
  pFromJSVal :: JSVal -> WebGLDrawBuffers
pFromJSVal = JSVal -> WebGLDrawBuffers
WebGLDrawBuffers
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLDrawBuffers where
  toJSVal :: WebGLDrawBuffers -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLDrawBuffers -> JSVal) -> WebGLDrawBuffers -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLDrawBuffers -> JSVal
unWebGLDrawBuffers
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLDrawBuffers where
  fromJSVal :: JSVal -> JSM (Maybe WebGLDrawBuffers)
fromJSVal JSVal
v = (JSVal -> WebGLDrawBuffers)
-> Maybe JSVal -> Maybe WebGLDrawBuffers
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLDrawBuffers
WebGLDrawBuffers (Maybe JSVal -> Maybe WebGLDrawBuffers)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLDrawBuffers)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLDrawBuffers
fromJSValUnchecked = WebGLDrawBuffers -> JSM WebGLDrawBuffers
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLDrawBuffers -> JSM WebGLDrawBuffers)
-> (JSVal -> WebGLDrawBuffers) -> JSVal -> JSM WebGLDrawBuffers
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLDrawBuffers
WebGLDrawBuffers
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLDrawBuffers where
  makeObject :: WebGLDrawBuffers -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLDrawBuffers -> JSVal) -> WebGLDrawBuffers -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLDrawBuffers -> JSVal
unWebGLDrawBuffers

instance IsGObject WebGLDrawBuffers where
  typeGType :: WebGLDrawBuffers -> JSM GType
typeGType WebGLDrawBuffers
_ = JSM GType
gTypeWebGLDrawBuffers
  {-# INLINE typeGType #-}

noWebGLDrawBuffers :: Maybe WebGLDrawBuffers
noWebGLDrawBuffers :: Maybe WebGLDrawBuffers
noWebGLDrawBuffers = Maybe WebGLDrawBuffers
forall a. Maybe a
Nothing
{-# INLINE noWebGLDrawBuffers #-}

gTypeWebGLDrawBuffers :: JSM GType
gTypeWebGLDrawBuffers :: JSM GType
gTypeWebGLDrawBuffers = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLDrawBuffers"

-- | Functions for this inteface are in "JSDOM.WebGLFramebuffer".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLFramebuffer Mozilla WebGLFramebuffer documentation>
newtype WebGLFramebuffer = WebGLFramebuffer { WebGLFramebuffer -> JSVal
unWebGLFramebuffer :: JSVal }

instance PToJSVal WebGLFramebuffer where
  pToJSVal :: WebGLFramebuffer -> JSVal
pToJSVal = WebGLFramebuffer -> JSVal
unWebGLFramebuffer
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLFramebuffer where
  pFromJSVal :: JSVal -> WebGLFramebuffer
pFromJSVal = JSVal -> WebGLFramebuffer
WebGLFramebuffer
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLFramebuffer where
  toJSVal :: WebGLFramebuffer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLFramebuffer -> JSVal) -> WebGLFramebuffer -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLFramebuffer -> JSVal
unWebGLFramebuffer
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLFramebuffer where
  fromJSVal :: JSVal -> JSM (Maybe WebGLFramebuffer)
fromJSVal JSVal
v = (JSVal -> WebGLFramebuffer)
-> Maybe JSVal -> Maybe WebGLFramebuffer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLFramebuffer
WebGLFramebuffer (Maybe JSVal -> Maybe WebGLFramebuffer)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLFramebuffer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLFramebuffer
fromJSValUnchecked = WebGLFramebuffer -> JSM WebGLFramebuffer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLFramebuffer -> JSM WebGLFramebuffer)
-> (JSVal -> WebGLFramebuffer) -> JSVal -> JSM WebGLFramebuffer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLFramebuffer
WebGLFramebuffer
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLFramebuffer where
  makeObject :: WebGLFramebuffer -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLFramebuffer -> JSVal) -> WebGLFramebuffer -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLFramebuffer -> JSVal
unWebGLFramebuffer

instance IsGObject WebGLFramebuffer where
  typeGType :: WebGLFramebuffer -> JSM GType
typeGType WebGLFramebuffer
_ = JSM GType
gTypeWebGLFramebuffer
  {-# INLINE typeGType #-}

noWebGLFramebuffer :: Maybe WebGLFramebuffer
noWebGLFramebuffer :: Maybe WebGLFramebuffer
noWebGLFramebuffer = Maybe WebGLFramebuffer
forall a. Maybe a
Nothing
{-# INLINE noWebGLFramebuffer #-}

gTypeWebGLFramebuffer :: JSM GType
gTypeWebGLFramebuffer :: JSM GType
gTypeWebGLFramebuffer = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLFramebuffer"

-- | Functions for this inteface are in "JSDOM.WebGLLoseContext".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLLoseContext Mozilla WebGLLoseContext documentation>
newtype WebGLLoseContext = WebGLLoseContext { WebGLLoseContext -> JSVal
unWebGLLoseContext :: JSVal }

instance PToJSVal WebGLLoseContext where
  pToJSVal :: WebGLLoseContext -> JSVal
pToJSVal = WebGLLoseContext -> JSVal
unWebGLLoseContext
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLLoseContext where
  pFromJSVal :: JSVal -> WebGLLoseContext
pFromJSVal = JSVal -> WebGLLoseContext
WebGLLoseContext
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLLoseContext where
  toJSVal :: WebGLLoseContext -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLLoseContext -> JSVal) -> WebGLLoseContext -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLLoseContext -> JSVal
unWebGLLoseContext
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLLoseContext where
  fromJSVal :: JSVal -> JSM (Maybe WebGLLoseContext)
fromJSVal JSVal
v = (JSVal -> WebGLLoseContext)
-> Maybe JSVal -> Maybe WebGLLoseContext
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLLoseContext
WebGLLoseContext (Maybe JSVal -> Maybe WebGLLoseContext)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLLoseContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLLoseContext
fromJSValUnchecked = WebGLLoseContext -> JSM WebGLLoseContext
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLLoseContext -> JSM WebGLLoseContext)
-> (JSVal -> WebGLLoseContext) -> JSVal -> JSM WebGLLoseContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLLoseContext
WebGLLoseContext
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLLoseContext where
  makeObject :: WebGLLoseContext -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLLoseContext -> JSVal) -> WebGLLoseContext -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLLoseContext -> JSVal
unWebGLLoseContext

instance IsGObject WebGLLoseContext where
  typeGType :: WebGLLoseContext -> JSM GType
typeGType WebGLLoseContext
_ = JSM GType
gTypeWebGLLoseContext
  {-# INLINE typeGType #-}

noWebGLLoseContext :: Maybe WebGLLoseContext
noWebGLLoseContext :: Maybe WebGLLoseContext
noWebGLLoseContext = Maybe WebGLLoseContext
forall a. Maybe a
Nothing
{-# INLINE noWebGLLoseContext #-}

gTypeWebGLLoseContext :: JSM GType
gTypeWebGLLoseContext :: JSM GType
gTypeWebGLLoseContext = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLLoseContext"

-- | Functions for this inteface are in "JSDOM.WebGLProgram".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLProgram Mozilla WebGLProgram documentation>
newtype WebGLProgram = WebGLProgram { WebGLProgram -> JSVal
unWebGLProgram :: JSVal }

instance PToJSVal WebGLProgram where
  pToJSVal :: WebGLProgram -> JSVal
pToJSVal = WebGLProgram -> JSVal
unWebGLProgram
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLProgram where
  pFromJSVal :: JSVal -> WebGLProgram
pFromJSVal = JSVal -> WebGLProgram
WebGLProgram
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLProgram where
  toJSVal :: WebGLProgram -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLProgram -> JSVal) -> WebGLProgram -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLProgram -> JSVal
unWebGLProgram
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLProgram where
  fromJSVal :: JSVal -> JSM (Maybe WebGLProgram)
fromJSVal JSVal
v = (JSVal -> WebGLProgram) -> Maybe JSVal -> Maybe WebGLProgram
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLProgram
WebGLProgram (Maybe JSVal -> Maybe WebGLProgram)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLProgram)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLProgram
fromJSValUnchecked = WebGLProgram -> JSM WebGLProgram
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLProgram -> JSM WebGLProgram)
-> (JSVal -> WebGLProgram) -> JSVal -> JSM WebGLProgram
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLProgram
WebGLProgram
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLProgram where
  makeObject :: WebGLProgram -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLProgram -> JSVal) -> WebGLProgram -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLProgram -> JSVal
unWebGLProgram

instance IsGObject WebGLProgram where
  typeGType :: WebGLProgram -> JSM GType
typeGType WebGLProgram
_ = JSM GType
gTypeWebGLProgram
  {-# INLINE typeGType #-}

noWebGLProgram :: Maybe WebGLProgram
noWebGLProgram :: Maybe WebGLProgram
noWebGLProgram = Maybe WebGLProgram
forall a. Maybe a
Nothing
{-# INLINE noWebGLProgram #-}

gTypeWebGLProgram :: JSM GType
gTypeWebGLProgram :: JSM GType
gTypeWebGLProgram = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLProgram"

-- | Functions for this inteface are in "JSDOM.WebGLQuery".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLQuery Mozilla WebGLQuery documentation>
newtype WebGLQuery = WebGLQuery { WebGLQuery -> JSVal
unWebGLQuery :: JSVal }

instance PToJSVal WebGLQuery where
  pToJSVal :: WebGLQuery -> JSVal
pToJSVal = WebGLQuery -> JSVal
unWebGLQuery
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLQuery where
  pFromJSVal :: JSVal -> WebGLQuery
pFromJSVal = JSVal -> WebGLQuery
WebGLQuery
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLQuery where
  toJSVal :: WebGLQuery -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLQuery -> JSVal) -> WebGLQuery -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLQuery -> JSVal
unWebGLQuery
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLQuery where
  fromJSVal :: JSVal -> JSM (Maybe WebGLQuery)
fromJSVal JSVal
v = (JSVal -> WebGLQuery) -> Maybe JSVal -> Maybe WebGLQuery
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLQuery
WebGLQuery (Maybe JSVal -> Maybe WebGLQuery)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLQuery)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLQuery
fromJSValUnchecked = WebGLQuery -> JSM WebGLQuery
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLQuery -> JSM WebGLQuery)
-> (JSVal -> WebGLQuery) -> JSVal -> JSM WebGLQuery
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLQuery
WebGLQuery
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLQuery where
  makeObject :: WebGLQuery -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLQuery -> JSVal) -> WebGLQuery -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLQuery -> JSVal
unWebGLQuery

instance IsGObject WebGLQuery where
  typeGType :: WebGLQuery -> JSM GType
typeGType WebGLQuery
_ = JSM GType
gTypeWebGLQuery
  {-# INLINE typeGType #-}

noWebGLQuery :: Maybe WebGLQuery
noWebGLQuery :: Maybe WebGLQuery
noWebGLQuery = Maybe WebGLQuery
forall a. Maybe a
Nothing
{-# INLINE noWebGLQuery #-}

gTypeWebGLQuery :: JSM GType
gTypeWebGLQuery :: JSM GType
gTypeWebGLQuery = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLQuery"

-- | Functions for this inteface are in "JSDOM.WebGLRenderbuffer".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLRenderbuffer Mozilla WebGLRenderbuffer documentation>
newtype WebGLRenderbuffer = WebGLRenderbuffer { WebGLRenderbuffer -> JSVal
unWebGLRenderbuffer :: JSVal }

instance PToJSVal WebGLRenderbuffer where
  pToJSVal :: WebGLRenderbuffer -> JSVal
pToJSVal = WebGLRenderbuffer -> JSVal
unWebGLRenderbuffer
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLRenderbuffer where
  pFromJSVal :: JSVal -> WebGLRenderbuffer
pFromJSVal = JSVal -> WebGLRenderbuffer
WebGLRenderbuffer
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLRenderbuffer where
  toJSVal :: WebGLRenderbuffer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLRenderbuffer -> JSVal) -> WebGLRenderbuffer -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLRenderbuffer -> JSVal
unWebGLRenderbuffer
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLRenderbuffer where
  fromJSVal :: JSVal -> JSM (Maybe WebGLRenderbuffer)
fromJSVal JSVal
v = (JSVal -> WebGLRenderbuffer)
-> Maybe JSVal -> Maybe WebGLRenderbuffer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLRenderbuffer
WebGLRenderbuffer (Maybe JSVal -> Maybe WebGLRenderbuffer)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLRenderbuffer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLRenderbuffer
fromJSValUnchecked = WebGLRenderbuffer -> JSM WebGLRenderbuffer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLRenderbuffer -> JSM WebGLRenderbuffer)
-> (JSVal -> WebGLRenderbuffer) -> JSVal -> JSM WebGLRenderbuffer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLRenderbuffer
WebGLRenderbuffer
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLRenderbuffer where
  makeObject :: WebGLRenderbuffer -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLRenderbuffer -> JSVal) -> WebGLRenderbuffer -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLRenderbuffer -> JSVal
unWebGLRenderbuffer

instance IsGObject WebGLRenderbuffer where
  typeGType :: WebGLRenderbuffer -> JSM GType
typeGType WebGLRenderbuffer
_ = JSM GType
gTypeWebGLRenderbuffer
  {-# INLINE typeGType #-}

noWebGLRenderbuffer :: Maybe WebGLRenderbuffer
noWebGLRenderbuffer :: Maybe WebGLRenderbuffer
noWebGLRenderbuffer = Maybe WebGLRenderbuffer
forall a. Maybe a
Nothing
{-# INLINE noWebGLRenderbuffer #-}

gTypeWebGLRenderbuffer :: JSM GType
gTypeWebGLRenderbuffer :: JSM GType
gTypeWebGLRenderbuffer = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLRenderbuffer"

-- | Functions for this inteface are in "JSDOM.WebGLRenderingContext".
-- Base interface functions are in:
--
--     * "JSDOM.WebGLRenderingContextBase"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLRenderingContext Mozilla WebGLRenderingContext documentation>
newtype WebGLRenderingContext = WebGLRenderingContext { WebGLRenderingContext -> JSVal
unWebGLRenderingContext :: JSVal }

instance PToJSVal WebGLRenderingContext where
  pToJSVal :: WebGLRenderingContext -> JSVal
pToJSVal = WebGLRenderingContext -> JSVal
unWebGLRenderingContext
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLRenderingContext where
  pFromJSVal :: JSVal -> WebGLRenderingContext
pFromJSVal = JSVal -> WebGLRenderingContext
WebGLRenderingContext
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLRenderingContext where
  toJSVal :: WebGLRenderingContext -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLRenderingContext -> JSVal)
-> WebGLRenderingContext
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLRenderingContext -> JSVal
unWebGLRenderingContext
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLRenderingContext where
  fromJSVal :: JSVal -> JSM (Maybe WebGLRenderingContext)
fromJSVal JSVal
v = (JSVal -> WebGLRenderingContext)
-> Maybe JSVal -> Maybe WebGLRenderingContext
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLRenderingContext
WebGLRenderingContext (Maybe JSVal -> Maybe WebGLRenderingContext)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLRenderingContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLRenderingContext
fromJSValUnchecked = WebGLRenderingContext -> JSM WebGLRenderingContext
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLRenderingContext -> JSM WebGLRenderingContext)
-> (JSVal -> WebGLRenderingContext)
-> JSVal
-> JSM WebGLRenderingContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLRenderingContext
WebGLRenderingContext
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLRenderingContext where
  makeObject :: WebGLRenderingContext -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLRenderingContext -> JSVal)
-> WebGLRenderingContext
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLRenderingContext -> JSVal
unWebGLRenderingContext

instance IsWebGLRenderingContextBase WebGLRenderingContext
instance IsGObject WebGLRenderingContext where
  typeGType :: WebGLRenderingContext -> JSM GType
typeGType WebGLRenderingContext
_ = JSM GType
gTypeWebGLRenderingContext
  {-# INLINE typeGType #-}

noWebGLRenderingContext :: Maybe WebGLRenderingContext
noWebGLRenderingContext :: Maybe WebGLRenderingContext
noWebGLRenderingContext = Maybe WebGLRenderingContext
forall a. Maybe a
Nothing
{-# INLINE noWebGLRenderingContext #-}

gTypeWebGLRenderingContext :: JSM GType
gTypeWebGLRenderingContext :: JSM GType
gTypeWebGLRenderingContext = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLRenderingContext"

-- | Functions for this inteface are in "JSDOM.WebGLRenderingContextBase".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLRenderingContextBase Mozilla WebGLRenderingContextBase documentation>
newtype WebGLRenderingContextBase = WebGLRenderingContextBase { WebGLRenderingContextBase -> JSVal
unWebGLRenderingContextBase :: JSVal }

instance PToJSVal WebGLRenderingContextBase where
  pToJSVal :: WebGLRenderingContextBase -> JSVal
pToJSVal = WebGLRenderingContextBase -> JSVal
unWebGLRenderingContextBase
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLRenderingContextBase where
  pFromJSVal :: JSVal -> WebGLRenderingContextBase
pFromJSVal = JSVal -> WebGLRenderingContextBase
WebGLRenderingContextBase
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLRenderingContextBase where
  toJSVal :: WebGLRenderingContextBase -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLRenderingContextBase -> JSVal)
-> WebGLRenderingContextBase
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLRenderingContextBase -> JSVal
unWebGLRenderingContextBase
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLRenderingContextBase where
  fromJSVal :: JSVal -> JSM (Maybe WebGLRenderingContextBase)
fromJSVal JSVal
v = (JSVal -> WebGLRenderingContextBase)
-> Maybe JSVal -> Maybe WebGLRenderingContextBase
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLRenderingContextBase
WebGLRenderingContextBase (Maybe JSVal -> Maybe WebGLRenderingContextBase)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLRenderingContextBase)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLRenderingContextBase
fromJSValUnchecked = WebGLRenderingContextBase -> JSM WebGLRenderingContextBase
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLRenderingContextBase -> JSM WebGLRenderingContextBase)
-> (JSVal -> WebGLRenderingContextBase)
-> JSVal
-> JSM WebGLRenderingContextBase
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLRenderingContextBase
WebGLRenderingContextBase
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLRenderingContextBase where
  makeObject :: WebGLRenderingContextBase -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLRenderingContextBase -> JSVal)
-> WebGLRenderingContextBase
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLRenderingContextBase -> JSVal
unWebGLRenderingContextBase

class (IsGObject o) => IsWebGLRenderingContextBase o
toWebGLRenderingContextBase :: IsWebGLRenderingContextBase o => o -> WebGLRenderingContextBase
toWebGLRenderingContextBase :: forall o.
IsWebGLRenderingContextBase o =>
o -> WebGLRenderingContextBase
toWebGLRenderingContextBase = JSVal -> WebGLRenderingContextBase
WebGLRenderingContextBase (JSVal -> WebGLRenderingContextBase)
-> (o -> JSVal) -> o -> WebGLRenderingContextBase
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsWebGLRenderingContextBase WebGLRenderingContextBase
instance IsGObject WebGLRenderingContextBase where
  typeGType :: WebGLRenderingContextBase -> JSM GType
typeGType WebGLRenderingContextBase
_ = JSM GType
gTypeWebGLRenderingContextBase
  {-# INLINE typeGType #-}

noWebGLRenderingContextBase :: Maybe WebGLRenderingContextBase
noWebGLRenderingContextBase :: Maybe WebGLRenderingContextBase
noWebGLRenderingContextBase = Maybe WebGLRenderingContextBase
forall a. Maybe a
Nothing
{-# INLINE noWebGLRenderingContextBase #-}

gTypeWebGLRenderingContextBase :: JSM GType
gTypeWebGLRenderingContextBase :: JSM GType
gTypeWebGLRenderingContextBase = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLRenderingContextBase"

-- | Functions for this inteface are in "JSDOM.WebGLSampler".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLSampler Mozilla WebGLSampler documentation>
newtype WebGLSampler = WebGLSampler { WebGLSampler -> JSVal
unWebGLSampler :: JSVal }

instance PToJSVal WebGLSampler where
  pToJSVal :: WebGLSampler -> JSVal
pToJSVal = WebGLSampler -> JSVal
unWebGLSampler
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLSampler where
  pFromJSVal :: JSVal -> WebGLSampler
pFromJSVal = JSVal -> WebGLSampler
WebGLSampler
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLSampler where
  toJSVal :: WebGLSampler -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLSampler -> JSVal) -> WebGLSampler -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLSampler -> JSVal
unWebGLSampler
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLSampler where
  fromJSVal :: JSVal -> JSM (Maybe WebGLSampler)
fromJSVal JSVal
v = (JSVal -> WebGLSampler) -> Maybe JSVal -> Maybe WebGLSampler
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLSampler
WebGLSampler (Maybe JSVal -> Maybe WebGLSampler)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLSampler)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLSampler
fromJSValUnchecked = WebGLSampler -> JSM WebGLSampler
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLSampler -> JSM WebGLSampler)
-> (JSVal -> WebGLSampler) -> JSVal -> JSM WebGLSampler
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLSampler
WebGLSampler
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLSampler where
  makeObject :: WebGLSampler -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLSampler -> JSVal) -> WebGLSampler -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLSampler -> JSVal
unWebGLSampler

instance IsGObject WebGLSampler where
  typeGType :: WebGLSampler -> JSM GType
typeGType WebGLSampler
_ = JSM GType
gTypeWebGLSampler
  {-# INLINE typeGType #-}

noWebGLSampler :: Maybe WebGLSampler
noWebGLSampler :: Maybe WebGLSampler
noWebGLSampler = Maybe WebGLSampler
forall a. Maybe a
Nothing
{-# INLINE noWebGLSampler #-}

gTypeWebGLSampler :: JSM GType
gTypeWebGLSampler :: JSM GType
gTypeWebGLSampler = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLSampler"

-- | Functions for this inteface are in "JSDOM.WebGLShader".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLShader Mozilla WebGLShader documentation>
newtype WebGLShader = WebGLShader { WebGLShader -> JSVal
unWebGLShader :: JSVal }

instance PToJSVal WebGLShader where
  pToJSVal :: WebGLShader -> JSVal
pToJSVal = WebGLShader -> JSVal
unWebGLShader
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLShader where
  pFromJSVal :: JSVal -> WebGLShader
pFromJSVal = JSVal -> WebGLShader
WebGLShader
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLShader where
  toJSVal :: WebGLShader -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLShader -> JSVal) -> WebGLShader -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLShader -> JSVal
unWebGLShader
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLShader where
  fromJSVal :: JSVal -> JSM (Maybe WebGLShader)
fromJSVal JSVal
v = (JSVal -> WebGLShader) -> Maybe JSVal -> Maybe WebGLShader
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLShader
WebGLShader (Maybe JSVal -> Maybe WebGLShader)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLShader)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLShader
fromJSValUnchecked = WebGLShader -> JSM WebGLShader
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLShader -> JSM WebGLShader)
-> (JSVal -> WebGLShader) -> JSVal -> JSM WebGLShader
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLShader
WebGLShader
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLShader where
  makeObject :: WebGLShader -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLShader -> JSVal) -> WebGLShader -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLShader -> JSVal
unWebGLShader

instance IsGObject WebGLShader where
  typeGType :: WebGLShader -> JSM GType
typeGType WebGLShader
_ = JSM GType
gTypeWebGLShader
  {-# INLINE typeGType #-}

noWebGLShader :: Maybe WebGLShader
noWebGLShader :: Maybe WebGLShader
noWebGLShader = Maybe WebGLShader
forall a. Maybe a
Nothing
{-# INLINE noWebGLShader #-}

gTypeWebGLShader :: JSM GType
gTypeWebGLShader :: JSM GType
gTypeWebGLShader = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLShader"

-- | Functions for this inteface are in "JSDOM.WebGLShaderPrecisionFormat".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLShaderPrecisionFormat Mozilla WebGLShaderPrecisionFormat documentation>
newtype WebGLShaderPrecisionFormat = WebGLShaderPrecisionFormat { WebGLShaderPrecisionFormat -> JSVal
unWebGLShaderPrecisionFormat :: JSVal }

instance PToJSVal WebGLShaderPrecisionFormat where
  pToJSVal :: WebGLShaderPrecisionFormat -> JSVal
pToJSVal = WebGLShaderPrecisionFormat -> JSVal
unWebGLShaderPrecisionFormat
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLShaderPrecisionFormat where
  pFromJSVal :: JSVal -> WebGLShaderPrecisionFormat
pFromJSVal = JSVal -> WebGLShaderPrecisionFormat
WebGLShaderPrecisionFormat
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLShaderPrecisionFormat where
  toJSVal :: WebGLShaderPrecisionFormat -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLShaderPrecisionFormat -> JSVal)
-> WebGLShaderPrecisionFormat
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLShaderPrecisionFormat -> JSVal
unWebGLShaderPrecisionFormat
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLShaderPrecisionFormat where
  fromJSVal :: JSVal -> JSM (Maybe WebGLShaderPrecisionFormat)
fromJSVal JSVal
v = (JSVal -> WebGLShaderPrecisionFormat)
-> Maybe JSVal -> Maybe WebGLShaderPrecisionFormat
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLShaderPrecisionFormat
WebGLShaderPrecisionFormat (Maybe JSVal -> Maybe WebGLShaderPrecisionFormat)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLShaderPrecisionFormat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLShaderPrecisionFormat
fromJSValUnchecked = WebGLShaderPrecisionFormat -> JSM WebGLShaderPrecisionFormat
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLShaderPrecisionFormat -> JSM WebGLShaderPrecisionFormat)
-> (JSVal -> WebGLShaderPrecisionFormat)
-> JSVal
-> JSM WebGLShaderPrecisionFormat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLShaderPrecisionFormat
WebGLShaderPrecisionFormat
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLShaderPrecisionFormat where
  makeObject :: WebGLShaderPrecisionFormat -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLShaderPrecisionFormat -> JSVal)
-> WebGLShaderPrecisionFormat
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLShaderPrecisionFormat -> JSVal
unWebGLShaderPrecisionFormat

instance IsGObject WebGLShaderPrecisionFormat where
  typeGType :: WebGLShaderPrecisionFormat -> JSM GType
typeGType WebGLShaderPrecisionFormat
_ = JSM GType
gTypeWebGLShaderPrecisionFormat
  {-# INLINE typeGType #-}

noWebGLShaderPrecisionFormat :: Maybe WebGLShaderPrecisionFormat
noWebGLShaderPrecisionFormat :: Maybe WebGLShaderPrecisionFormat
noWebGLShaderPrecisionFormat = Maybe WebGLShaderPrecisionFormat
forall a. Maybe a
Nothing
{-# INLINE noWebGLShaderPrecisionFormat #-}

gTypeWebGLShaderPrecisionFormat :: JSM GType
gTypeWebGLShaderPrecisionFormat :: JSM GType
gTypeWebGLShaderPrecisionFormat = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLShaderPrecisionFormat"

-- | Functions for this inteface are in "JSDOM.WebGLSync".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLSync Mozilla WebGLSync documentation>
newtype WebGLSync = WebGLSync { WebGLSync -> JSVal
unWebGLSync :: JSVal }

instance PToJSVal WebGLSync where
  pToJSVal :: WebGLSync -> JSVal
pToJSVal = WebGLSync -> JSVal
unWebGLSync
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLSync where
  pFromJSVal :: JSVal -> WebGLSync
pFromJSVal = JSVal -> WebGLSync
WebGLSync
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLSync where
  toJSVal :: WebGLSync -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLSync -> JSVal) -> WebGLSync -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLSync -> JSVal
unWebGLSync
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLSync where
  fromJSVal :: JSVal -> JSM (Maybe WebGLSync)
fromJSVal JSVal
v = (JSVal -> WebGLSync) -> Maybe JSVal -> Maybe WebGLSync
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLSync
WebGLSync (Maybe JSVal -> Maybe WebGLSync)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLSync)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLSync
fromJSValUnchecked = WebGLSync -> JSM WebGLSync
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLSync -> JSM WebGLSync)
-> (JSVal -> WebGLSync) -> JSVal -> JSM WebGLSync
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLSync
WebGLSync
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLSync where
  makeObject :: WebGLSync -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLSync -> JSVal) -> WebGLSync -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLSync -> JSVal
unWebGLSync

instance IsGObject WebGLSync where
  typeGType :: WebGLSync -> JSM GType
typeGType WebGLSync
_ = JSM GType
gTypeWebGLSync
  {-# INLINE typeGType #-}

noWebGLSync :: Maybe WebGLSync
noWebGLSync :: Maybe WebGLSync
noWebGLSync = Maybe WebGLSync
forall a. Maybe a
Nothing
{-# INLINE noWebGLSync #-}

gTypeWebGLSync :: JSM GType
gTypeWebGLSync :: JSM GType
gTypeWebGLSync = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLSync"

-- | Functions for this inteface are in "JSDOM.WebGLTexture".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLTexture Mozilla WebGLTexture documentation>
newtype WebGLTexture = WebGLTexture { WebGLTexture -> JSVal
unWebGLTexture :: JSVal }

instance PToJSVal WebGLTexture where
  pToJSVal :: WebGLTexture -> JSVal
pToJSVal = WebGLTexture -> JSVal
unWebGLTexture
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLTexture where
  pFromJSVal :: JSVal -> WebGLTexture
pFromJSVal = JSVal -> WebGLTexture
WebGLTexture
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLTexture where
  toJSVal :: WebGLTexture -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLTexture -> JSVal) -> WebGLTexture -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLTexture -> JSVal
unWebGLTexture
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLTexture where
  fromJSVal :: JSVal -> JSM (Maybe WebGLTexture)
fromJSVal JSVal
v = (JSVal -> WebGLTexture) -> Maybe JSVal -> Maybe WebGLTexture
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLTexture
WebGLTexture (Maybe JSVal -> Maybe WebGLTexture)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLTexture)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLTexture
fromJSValUnchecked = WebGLTexture -> JSM WebGLTexture
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLTexture -> JSM WebGLTexture)
-> (JSVal -> WebGLTexture) -> JSVal -> JSM WebGLTexture
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLTexture
WebGLTexture
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLTexture where
  makeObject :: WebGLTexture -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLTexture -> JSVal) -> WebGLTexture -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLTexture -> JSVal
unWebGLTexture

instance IsGObject WebGLTexture where
  typeGType :: WebGLTexture -> JSM GType
typeGType WebGLTexture
_ = JSM GType
gTypeWebGLTexture
  {-# INLINE typeGType #-}

noWebGLTexture :: Maybe WebGLTexture
noWebGLTexture :: Maybe WebGLTexture
noWebGLTexture = Maybe WebGLTexture
forall a. Maybe a
Nothing
{-# INLINE noWebGLTexture #-}

gTypeWebGLTexture :: JSM GType
gTypeWebGLTexture :: JSM GType
gTypeWebGLTexture = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLTexture"

-- | Functions for this inteface are in "JSDOM.WebGLTransformFeedback".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLTransformFeedback Mozilla WebGLTransformFeedback documentation>
newtype WebGLTransformFeedback = WebGLTransformFeedback { WebGLTransformFeedback -> JSVal
unWebGLTransformFeedback :: JSVal }

instance PToJSVal WebGLTransformFeedback where
  pToJSVal :: WebGLTransformFeedback -> JSVal
pToJSVal = WebGLTransformFeedback -> JSVal
unWebGLTransformFeedback
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLTransformFeedback where
  pFromJSVal :: JSVal -> WebGLTransformFeedback
pFromJSVal = JSVal -> WebGLTransformFeedback
WebGLTransformFeedback
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLTransformFeedback where
  toJSVal :: WebGLTransformFeedback -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLTransformFeedback -> JSVal)
-> WebGLTransformFeedback
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLTransformFeedback -> JSVal
unWebGLTransformFeedback
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLTransformFeedback where
  fromJSVal :: JSVal -> JSM (Maybe WebGLTransformFeedback)
fromJSVal JSVal
v = (JSVal -> WebGLTransformFeedback)
-> Maybe JSVal -> Maybe WebGLTransformFeedback
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLTransformFeedback
WebGLTransformFeedback (Maybe JSVal -> Maybe WebGLTransformFeedback)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLTransformFeedback)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLTransformFeedback
fromJSValUnchecked = WebGLTransformFeedback -> JSM WebGLTransformFeedback
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLTransformFeedback -> JSM WebGLTransformFeedback)
-> (JSVal -> WebGLTransformFeedback)
-> JSVal
-> JSM WebGLTransformFeedback
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLTransformFeedback
WebGLTransformFeedback
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLTransformFeedback where
  makeObject :: WebGLTransformFeedback -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLTransformFeedback -> JSVal)
-> WebGLTransformFeedback
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLTransformFeedback -> JSVal
unWebGLTransformFeedback

instance IsGObject WebGLTransformFeedback where
  typeGType :: WebGLTransformFeedback -> JSM GType
typeGType WebGLTransformFeedback
_ = JSM GType
gTypeWebGLTransformFeedback
  {-# INLINE typeGType #-}

noWebGLTransformFeedback :: Maybe WebGLTransformFeedback
noWebGLTransformFeedback :: Maybe WebGLTransformFeedback
noWebGLTransformFeedback = Maybe WebGLTransformFeedback
forall a. Maybe a
Nothing
{-# INLINE noWebGLTransformFeedback #-}

gTypeWebGLTransformFeedback :: JSM GType
gTypeWebGLTransformFeedback :: JSM GType
gTypeWebGLTransformFeedback = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLTransformFeedback"

-- | Functions for this inteface are in "JSDOM.WebGLUniformLocation".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLUniformLocation Mozilla WebGLUniformLocation documentation>
newtype WebGLUniformLocation = WebGLUniformLocation { WebGLUniformLocation -> JSVal
unWebGLUniformLocation :: JSVal }

instance PToJSVal WebGLUniformLocation where
  pToJSVal :: WebGLUniformLocation -> JSVal
pToJSVal = WebGLUniformLocation -> JSVal
unWebGLUniformLocation
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLUniformLocation where
  pFromJSVal :: JSVal -> WebGLUniformLocation
pFromJSVal = JSVal -> WebGLUniformLocation
WebGLUniformLocation
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLUniformLocation where
  toJSVal :: WebGLUniformLocation -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLUniformLocation -> JSVal)
-> WebGLUniformLocation
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLUniformLocation -> JSVal
unWebGLUniformLocation
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLUniformLocation where
  fromJSVal :: JSVal -> JSM (Maybe WebGLUniformLocation)
fromJSVal JSVal
v = (JSVal -> WebGLUniformLocation)
-> Maybe JSVal -> Maybe WebGLUniformLocation
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLUniformLocation
WebGLUniformLocation (Maybe JSVal -> Maybe WebGLUniformLocation)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLUniformLocation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLUniformLocation
fromJSValUnchecked = WebGLUniformLocation -> JSM WebGLUniformLocation
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLUniformLocation -> JSM WebGLUniformLocation)
-> (JSVal -> WebGLUniformLocation)
-> JSVal
-> JSM WebGLUniformLocation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLUniformLocation
WebGLUniformLocation
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLUniformLocation where
  makeObject :: WebGLUniformLocation -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLUniformLocation -> JSVal)
-> WebGLUniformLocation
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLUniformLocation -> JSVal
unWebGLUniformLocation

instance IsGObject WebGLUniformLocation where
  typeGType :: WebGLUniformLocation -> JSM GType
typeGType WebGLUniformLocation
_ = JSM GType
gTypeWebGLUniformLocation
  {-# INLINE typeGType #-}

noWebGLUniformLocation :: Maybe WebGLUniformLocation
noWebGLUniformLocation :: Maybe WebGLUniformLocation
noWebGLUniformLocation = Maybe WebGLUniformLocation
forall a. Maybe a
Nothing
{-# INLINE noWebGLUniformLocation #-}

gTypeWebGLUniformLocation :: JSM GType
gTypeWebGLUniformLocation :: JSM GType
gTypeWebGLUniformLocation = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLUniformLocation"

-- | Functions for this inteface are in "JSDOM.WebGLVertexArrayObject".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLVertexArrayObject Mozilla WebGLVertexArrayObject documentation>
newtype WebGLVertexArrayObject = WebGLVertexArrayObject { WebGLVertexArrayObject -> JSVal
unWebGLVertexArrayObject :: JSVal }

instance PToJSVal WebGLVertexArrayObject where
  pToJSVal :: WebGLVertexArrayObject -> JSVal
pToJSVal = WebGLVertexArrayObject -> JSVal
unWebGLVertexArrayObject
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLVertexArrayObject where
  pFromJSVal :: JSVal -> WebGLVertexArrayObject
pFromJSVal = JSVal -> WebGLVertexArrayObject
WebGLVertexArrayObject
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLVertexArrayObject where
  toJSVal :: WebGLVertexArrayObject -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLVertexArrayObject -> JSVal)
-> WebGLVertexArrayObject
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLVertexArrayObject -> JSVal
unWebGLVertexArrayObject
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLVertexArrayObject where
  fromJSVal :: JSVal -> JSM (Maybe WebGLVertexArrayObject)
fromJSVal JSVal
v = (JSVal -> WebGLVertexArrayObject)
-> Maybe JSVal -> Maybe WebGLVertexArrayObject
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLVertexArrayObject
WebGLVertexArrayObject (Maybe JSVal -> Maybe WebGLVertexArrayObject)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLVertexArrayObject)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLVertexArrayObject
fromJSValUnchecked = WebGLVertexArrayObject -> JSM WebGLVertexArrayObject
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLVertexArrayObject -> JSM WebGLVertexArrayObject)
-> (JSVal -> WebGLVertexArrayObject)
-> JSVal
-> JSM WebGLVertexArrayObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLVertexArrayObject
WebGLVertexArrayObject
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLVertexArrayObject where
  makeObject :: WebGLVertexArrayObject -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLVertexArrayObject -> JSVal)
-> WebGLVertexArrayObject
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLVertexArrayObject -> JSVal
unWebGLVertexArrayObject

instance IsGObject WebGLVertexArrayObject where
  typeGType :: WebGLVertexArrayObject -> JSM GType
typeGType WebGLVertexArrayObject
_ = JSM GType
gTypeWebGLVertexArrayObject
  {-# INLINE typeGType #-}

noWebGLVertexArrayObject :: Maybe WebGLVertexArrayObject
noWebGLVertexArrayObject :: Maybe WebGLVertexArrayObject
noWebGLVertexArrayObject = Maybe WebGLVertexArrayObject
forall a. Maybe a
Nothing
{-# INLINE noWebGLVertexArrayObject #-}

gTypeWebGLVertexArrayObject :: JSM GType
gTypeWebGLVertexArrayObject :: JSM GType
gTypeWebGLVertexArrayObject = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLVertexArrayObject"

-- | Functions for this inteface are in "JSDOM.WebGLVertexArrayObjectOES".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGLVertexArrayObjectOES Mozilla WebGLVertexArrayObjectOES documentation>
newtype WebGLVertexArrayObjectOES = WebGLVertexArrayObjectOES { WebGLVertexArrayObjectOES -> JSVal
unWebGLVertexArrayObjectOES :: JSVal }

instance PToJSVal WebGLVertexArrayObjectOES where
  pToJSVal :: WebGLVertexArrayObjectOES -> JSVal
pToJSVal = WebGLVertexArrayObjectOES -> JSVal
unWebGLVertexArrayObjectOES
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGLVertexArrayObjectOES where
  pFromJSVal :: JSVal -> WebGLVertexArrayObjectOES
pFromJSVal = JSVal -> WebGLVertexArrayObjectOES
WebGLVertexArrayObjectOES
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGLVertexArrayObjectOES where
  toJSVal :: WebGLVertexArrayObjectOES -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGLVertexArrayObjectOES -> JSVal)
-> WebGLVertexArrayObjectOES
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLVertexArrayObjectOES -> JSVal
unWebGLVertexArrayObjectOES
  {-# INLINE toJSVal #-}

instance FromJSVal WebGLVertexArrayObjectOES where
  fromJSVal :: JSVal -> JSM (Maybe WebGLVertexArrayObjectOES)
fromJSVal JSVal
v = (JSVal -> WebGLVertexArrayObjectOES)
-> Maybe JSVal -> Maybe WebGLVertexArrayObjectOES
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGLVertexArrayObjectOES
WebGLVertexArrayObjectOES (Maybe JSVal -> Maybe WebGLVertexArrayObjectOES)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGLVertexArrayObjectOES)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGLVertexArrayObjectOES
fromJSValUnchecked = WebGLVertexArrayObjectOES -> JSM WebGLVertexArrayObjectOES
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLVertexArrayObjectOES -> JSM WebGLVertexArrayObjectOES)
-> (JSVal -> WebGLVertexArrayObjectOES)
-> JSVal
-> JSM WebGLVertexArrayObjectOES
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGLVertexArrayObjectOES
WebGLVertexArrayObjectOES
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGLVertexArrayObjectOES where
  makeObject :: WebGLVertexArrayObjectOES -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGLVertexArrayObjectOES -> JSVal)
-> WebGLVertexArrayObjectOES
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGLVertexArrayObjectOES -> JSVal
unWebGLVertexArrayObjectOES

instance IsGObject WebGLVertexArrayObjectOES where
  typeGType :: WebGLVertexArrayObjectOES -> JSM GType
typeGType WebGLVertexArrayObjectOES
_ = JSM GType
gTypeWebGLVertexArrayObjectOES
  {-# INLINE typeGType #-}

noWebGLVertexArrayObjectOES :: Maybe WebGLVertexArrayObjectOES
noWebGLVertexArrayObjectOES :: Maybe WebGLVertexArrayObjectOES
noWebGLVertexArrayObjectOES = Maybe WebGLVertexArrayObjectOES
forall a. Maybe a
Nothing
{-# INLINE noWebGLVertexArrayObjectOES #-}

gTypeWebGLVertexArrayObjectOES :: JSM GType
gTypeWebGLVertexArrayObjectOES :: JSM GType
gTypeWebGLVertexArrayObjectOES = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGLVertexArrayObjectOES"

-- | Functions for this inteface are in "JSDOM.WebGPUBuffer".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUBuffer Mozilla WebGPUBuffer documentation>
newtype WebGPUBuffer = WebGPUBuffer { WebGPUBuffer -> JSVal
unWebGPUBuffer :: JSVal }

instance PToJSVal WebGPUBuffer where
  pToJSVal :: WebGPUBuffer -> JSVal
pToJSVal = WebGPUBuffer -> JSVal
unWebGPUBuffer
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUBuffer where
  pFromJSVal :: JSVal -> WebGPUBuffer
pFromJSVal = JSVal -> WebGPUBuffer
WebGPUBuffer
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUBuffer where
  toJSVal :: WebGPUBuffer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUBuffer -> JSVal) -> WebGPUBuffer -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUBuffer -> JSVal
unWebGPUBuffer
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUBuffer where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUBuffer)
fromJSVal JSVal
v = (JSVal -> WebGPUBuffer) -> Maybe JSVal -> Maybe WebGPUBuffer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUBuffer
WebGPUBuffer (Maybe JSVal -> Maybe WebGPUBuffer)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUBuffer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUBuffer
fromJSValUnchecked = WebGPUBuffer -> JSM WebGPUBuffer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUBuffer -> JSM WebGPUBuffer)
-> (JSVal -> WebGPUBuffer) -> JSVal -> JSM WebGPUBuffer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUBuffer
WebGPUBuffer
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUBuffer where
  makeObject :: WebGPUBuffer -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUBuffer -> JSVal) -> WebGPUBuffer -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUBuffer -> JSVal
unWebGPUBuffer

instance IsGObject WebGPUBuffer where
  typeGType :: WebGPUBuffer -> JSM GType
typeGType WebGPUBuffer
_ = JSM GType
gTypeWebGPUBuffer
  {-# INLINE typeGType #-}

noWebGPUBuffer :: Maybe WebGPUBuffer
noWebGPUBuffer :: Maybe WebGPUBuffer
noWebGPUBuffer = Maybe WebGPUBuffer
forall a. Maybe a
Nothing
{-# INLINE noWebGPUBuffer #-}

gTypeWebGPUBuffer :: JSM GType
gTypeWebGPUBuffer :: JSM GType
gTypeWebGPUBuffer = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUBuffer"

-- | Functions for this inteface are in "JSDOM.WebGPUCommandBuffer".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUCommandBuffer Mozilla WebGPUCommandBuffer documentation>
newtype WebGPUCommandBuffer = WebGPUCommandBuffer { WebGPUCommandBuffer -> JSVal
unWebGPUCommandBuffer :: JSVal }

instance PToJSVal WebGPUCommandBuffer where
  pToJSVal :: WebGPUCommandBuffer -> JSVal
pToJSVal = WebGPUCommandBuffer -> JSVal
unWebGPUCommandBuffer
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUCommandBuffer where
  pFromJSVal :: JSVal -> WebGPUCommandBuffer
pFromJSVal = JSVal -> WebGPUCommandBuffer
WebGPUCommandBuffer
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUCommandBuffer where
  toJSVal :: WebGPUCommandBuffer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUCommandBuffer -> JSVal)
-> WebGPUCommandBuffer
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUCommandBuffer -> JSVal
unWebGPUCommandBuffer
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUCommandBuffer where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUCommandBuffer)
fromJSVal JSVal
v = (JSVal -> WebGPUCommandBuffer)
-> Maybe JSVal -> Maybe WebGPUCommandBuffer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUCommandBuffer
WebGPUCommandBuffer (Maybe JSVal -> Maybe WebGPUCommandBuffer)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUCommandBuffer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUCommandBuffer
fromJSValUnchecked = WebGPUCommandBuffer -> JSM WebGPUCommandBuffer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUCommandBuffer -> JSM WebGPUCommandBuffer)
-> (JSVal -> WebGPUCommandBuffer)
-> JSVal
-> JSM WebGPUCommandBuffer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUCommandBuffer
WebGPUCommandBuffer
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUCommandBuffer where
  makeObject :: WebGPUCommandBuffer -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUCommandBuffer -> JSVal)
-> WebGPUCommandBuffer
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUCommandBuffer -> JSVal
unWebGPUCommandBuffer

instance IsGObject WebGPUCommandBuffer where
  typeGType :: WebGPUCommandBuffer -> JSM GType
typeGType WebGPUCommandBuffer
_ = JSM GType
gTypeWebGPUCommandBuffer
  {-# INLINE typeGType #-}

noWebGPUCommandBuffer :: Maybe WebGPUCommandBuffer
noWebGPUCommandBuffer :: Maybe WebGPUCommandBuffer
noWebGPUCommandBuffer = Maybe WebGPUCommandBuffer
forall a. Maybe a
Nothing
{-# INLINE noWebGPUCommandBuffer #-}

gTypeWebGPUCommandBuffer :: JSM GType
gTypeWebGPUCommandBuffer :: JSM GType
gTypeWebGPUCommandBuffer = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUCommandBuffer"

-- | Functions for this inteface are in "JSDOM.WebGPUCommandQueue".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUCommandQueue Mozilla WebGPUCommandQueue documentation>
newtype WebGPUCommandQueue = WebGPUCommandQueue { WebGPUCommandQueue -> JSVal
unWebGPUCommandQueue :: JSVal }

instance PToJSVal WebGPUCommandQueue where
  pToJSVal :: WebGPUCommandQueue -> JSVal
pToJSVal = WebGPUCommandQueue -> JSVal
unWebGPUCommandQueue
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUCommandQueue where
  pFromJSVal :: JSVal -> WebGPUCommandQueue
pFromJSVal = JSVal -> WebGPUCommandQueue
WebGPUCommandQueue
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUCommandQueue where
  toJSVal :: WebGPUCommandQueue -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUCommandQueue -> JSVal) -> WebGPUCommandQueue -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUCommandQueue -> JSVal
unWebGPUCommandQueue
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUCommandQueue where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUCommandQueue)
fromJSVal JSVal
v = (JSVal -> WebGPUCommandQueue)
-> Maybe JSVal -> Maybe WebGPUCommandQueue
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUCommandQueue
WebGPUCommandQueue (Maybe JSVal -> Maybe WebGPUCommandQueue)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUCommandQueue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUCommandQueue
fromJSValUnchecked = WebGPUCommandQueue -> JSM WebGPUCommandQueue
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUCommandQueue -> JSM WebGPUCommandQueue)
-> (JSVal -> WebGPUCommandQueue) -> JSVal -> JSM WebGPUCommandQueue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUCommandQueue
WebGPUCommandQueue
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUCommandQueue where
  makeObject :: WebGPUCommandQueue -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUCommandQueue -> JSVal)
-> WebGPUCommandQueue
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUCommandQueue -> JSVal
unWebGPUCommandQueue

instance IsGObject WebGPUCommandQueue where
  typeGType :: WebGPUCommandQueue -> JSM GType
typeGType WebGPUCommandQueue
_ = JSM GType
gTypeWebGPUCommandQueue
  {-# INLINE typeGType #-}

noWebGPUCommandQueue :: Maybe WebGPUCommandQueue
noWebGPUCommandQueue :: Maybe WebGPUCommandQueue
noWebGPUCommandQueue = Maybe WebGPUCommandQueue
forall a. Maybe a
Nothing
{-# INLINE noWebGPUCommandQueue #-}

gTypeWebGPUCommandQueue :: JSM GType
gTypeWebGPUCommandQueue :: JSM GType
gTypeWebGPUCommandQueue = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUCommandQueue"

-- | Functions for this inteface are in "JSDOM.WebGPUComputeCommandEncoder".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUComputeCommandEncoder Mozilla WebGPUComputeCommandEncoder documentation>
newtype WebGPUComputeCommandEncoder = WebGPUComputeCommandEncoder { WebGPUComputeCommandEncoder -> JSVal
unWebGPUComputeCommandEncoder :: JSVal }

instance PToJSVal WebGPUComputeCommandEncoder where
  pToJSVal :: WebGPUComputeCommandEncoder -> JSVal
pToJSVal = WebGPUComputeCommandEncoder -> JSVal
unWebGPUComputeCommandEncoder
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUComputeCommandEncoder where
  pFromJSVal :: JSVal -> WebGPUComputeCommandEncoder
pFromJSVal = JSVal -> WebGPUComputeCommandEncoder
WebGPUComputeCommandEncoder
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUComputeCommandEncoder where
  toJSVal :: WebGPUComputeCommandEncoder -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUComputeCommandEncoder -> JSVal)
-> WebGPUComputeCommandEncoder
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUComputeCommandEncoder -> JSVal
unWebGPUComputeCommandEncoder
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUComputeCommandEncoder where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUComputeCommandEncoder)
fromJSVal JSVal
v = (JSVal -> WebGPUComputeCommandEncoder)
-> Maybe JSVal -> Maybe WebGPUComputeCommandEncoder
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUComputeCommandEncoder
WebGPUComputeCommandEncoder (Maybe JSVal -> Maybe WebGPUComputeCommandEncoder)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUComputeCommandEncoder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUComputeCommandEncoder
fromJSValUnchecked = WebGPUComputeCommandEncoder -> JSM WebGPUComputeCommandEncoder
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUComputeCommandEncoder -> JSM WebGPUComputeCommandEncoder)
-> (JSVal -> WebGPUComputeCommandEncoder)
-> JSVal
-> JSM WebGPUComputeCommandEncoder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUComputeCommandEncoder
WebGPUComputeCommandEncoder
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUComputeCommandEncoder where
  makeObject :: WebGPUComputeCommandEncoder -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUComputeCommandEncoder -> JSVal)
-> WebGPUComputeCommandEncoder
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUComputeCommandEncoder -> JSVal
unWebGPUComputeCommandEncoder

instance IsGObject WebGPUComputeCommandEncoder where
  typeGType :: WebGPUComputeCommandEncoder -> JSM GType
typeGType WebGPUComputeCommandEncoder
_ = JSM GType
gTypeWebGPUComputeCommandEncoder
  {-# INLINE typeGType #-}

noWebGPUComputeCommandEncoder :: Maybe WebGPUComputeCommandEncoder
noWebGPUComputeCommandEncoder :: Maybe WebGPUComputeCommandEncoder
noWebGPUComputeCommandEncoder = Maybe WebGPUComputeCommandEncoder
forall a. Maybe a
Nothing
{-# INLINE noWebGPUComputeCommandEncoder #-}

gTypeWebGPUComputeCommandEncoder :: JSM GType
gTypeWebGPUComputeCommandEncoder :: JSM GType
gTypeWebGPUComputeCommandEncoder = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUComputeCommandEncoder"

-- | Functions for this inteface are in "JSDOM.WebGPUComputePipelineState".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUComputePipelineState Mozilla WebGPUComputePipelineState documentation>
newtype WebGPUComputePipelineState = WebGPUComputePipelineState { WebGPUComputePipelineState -> JSVal
unWebGPUComputePipelineState :: JSVal }

instance PToJSVal WebGPUComputePipelineState where
  pToJSVal :: WebGPUComputePipelineState -> JSVal
pToJSVal = WebGPUComputePipelineState -> JSVal
unWebGPUComputePipelineState
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUComputePipelineState where
  pFromJSVal :: JSVal -> WebGPUComputePipelineState
pFromJSVal = JSVal -> WebGPUComputePipelineState
WebGPUComputePipelineState
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUComputePipelineState where
  toJSVal :: WebGPUComputePipelineState -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUComputePipelineState -> JSVal)
-> WebGPUComputePipelineState
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUComputePipelineState -> JSVal
unWebGPUComputePipelineState
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUComputePipelineState where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUComputePipelineState)
fromJSVal JSVal
v = (JSVal -> WebGPUComputePipelineState)
-> Maybe JSVal -> Maybe WebGPUComputePipelineState
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUComputePipelineState
WebGPUComputePipelineState (Maybe JSVal -> Maybe WebGPUComputePipelineState)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUComputePipelineState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUComputePipelineState
fromJSValUnchecked = WebGPUComputePipelineState -> JSM WebGPUComputePipelineState
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUComputePipelineState -> JSM WebGPUComputePipelineState)
-> (JSVal -> WebGPUComputePipelineState)
-> JSVal
-> JSM WebGPUComputePipelineState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUComputePipelineState
WebGPUComputePipelineState
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUComputePipelineState where
  makeObject :: WebGPUComputePipelineState -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUComputePipelineState -> JSVal)
-> WebGPUComputePipelineState
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUComputePipelineState -> JSVal
unWebGPUComputePipelineState

instance IsGObject WebGPUComputePipelineState where
  typeGType :: WebGPUComputePipelineState -> JSM GType
typeGType WebGPUComputePipelineState
_ = JSM GType
gTypeWebGPUComputePipelineState
  {-# INLINE typeGType #-}

noWebGPUComputePipelineState :: Maybe WebGPUComputePipelineState
noWebGPUComputePipelineState :: Maybe WebGPUComputePipelineState
noWebGPUComputePipelineState = Maybe WebGPUComputePipelineState
forall a. Maybe a
Nothing
{-# INLINE noWebGPUComputePipelineState #-}

gTypeWebGPUComputePipelineState :: JSM GType
gTypeWebGPUComputePipelineState :: JSM GType
gTypeWebGPUComputePipelineState = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUComputePipelineState"

-- | Functions for this inteface are in "JSDOM.WebGPUDepthStencilDescriptor".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUDepthStencilDescriptor Mozilla WebGPUDepthStencilDescriptor documentation>
newtype WebGPUDepthStencilDescriptor = WebGPUDepthStencilDescriptor { WebGPUDepthStencilDescriptor -> JSVal
unWebGPUDepthStencilDescriptor :: JSVal }

instance PToJSVal WebGPUDepthStencilDescriptor where
  pToJSVal :: WebGPUDepthStencilDescriptor -> JSVal
pToJSVal = WebGPUDepthStencilDescriptor -> JSVal
unWebGPUDepthStencilDescriptor
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUDepthStencilDescriptor where
  pFromJSVal :: JSVal -> WebGPUDepthStencilDescriptor
pFromJSVal = JSVal -> WebGPUDepthStencilDescriptor
WebGPUDepthStencilDescriptor
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUDepthStencilDescriptor where
  toJSVal :: WebGPUDepthStencilDescriptor -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUDepthStencilDescriptor -> JSVal)
-> WebGPUDepthStencilDescriptor
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUDepthStencilDescriptor -> JSVal
unWebGPUDepthStencilDescriptor
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUDepthStencilDescriptor where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUDepthStencilDescriptor)
fromJSVal JSVal
v = (JSVal -> WebGPUDepthStencilDescriptor)
-> Maybe JSVal -> Maybe WebGPUDepthStencilDescriptor
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUDepthStencilDescriptor
WebGPUDepthStencilDescriptor (Maybe JSVal -> Maybe WebGPUDepthStencilDescriptor)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUDepthStencilDescriptor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUDepthStencilDescriptor
fromJSValUnchecked = WebGPUDepthStencilDescriptor -> JSM WebGPUDepthStencilDescriptor
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUDepthStencilDescriptor -> JSM WebGPUDepthStencilDescriptor)
-> (JSVal -> WebGPUDepthStencilDescriptor)
-> JSVal
-> JSM WebGPUDepthStencilDescriptor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUDepthStencilDescriptor
WebGPUDepthStencilDescriptor
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUDepthStencilDescriptor where
  makeObject :: WebGPUDepthStencilDescriptor -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUDepthStencilDescriptor -> JSVal)
-> WebGPUDepthStencilDescriptor
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUDepthStencilDescriptor -> JSVal
unWebGPUDepthStencilDescriptor

instance IsGObject WebGPUDepthStencilDescriptor where
  typeGType :: WebGPUDepthStencilDescriptor -> JSM GType
typeGType WebGPUDepthStencilDescriptor
_ = JSM GType
gTypeWebGPUDepthStencilDescriptor
  {-# INLINE typeGType #-}

noWebGPUDepthStencilDescriptor :: Maybe WebGPUDepthStencilDescriptor
noWebGPUDepthStencilDescriptor :: Maybe WebGPUDepthStencilDescriptor
noWebGPUDepthStencilDescriptor = Maybe WebGPUDepthStencilDescriptor
forall a. Maybe a
Nothing
{-# INLINE noWebGPUDepthStencilDescriptor #-}

gTypeWebGPUDepthStencilDescriptor :: JSM GType
gTypeWebGPUDepthStencilDescriptor :: JSM GType
gTypeWebGPUDepthStencilDescriptor = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUDepthStencilDescriptor"

-- | Functions for this inteface are in "JSDOM.WebGPUDepthStencilState".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUDepthStencilState Mozilla WebGPUDepthStencilState documentation>
newtype WebGPUDepthStencilState = WebGPUDepthStencilState { WebGPUDepthStencilState -> JSVal
unWebGPUDepthStencilState :: JSVal }

instance PToJSVal WebGPUDepthStencilState where
  pToJSVal :: WebGPUDepthStencilState -> JSVal
pToJSVal = WebGPUDepthStencilState -> JSVal
unWebGPUDepthStencilState
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUDepthStencilState where
  pFromJSVal :: JSVal -> WebGPUDepthStencilState
pFromJSVal = JSVal -> WebGPUDepthStencilState
WebGPUDepthStencilState
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUDepthStencilState where
  toJSVal :: WebGPUDepthStencilState -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUDepthStencilState -> JSVal)
-> WebGPUDepthStencilState
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUDepthStencilState -> JSVal
unWebGPUDepthStencilState
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUDepthStencilState where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUDepthStencilState)
fromJSVal JSVal
v = (JSVal -> WebGPUDepthStencilState)
-> Maybe JSVal -> Maybe WebGPUDepthStencilState
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUDepthStencilState
WebGPUDepthStencilState (Maybe JSVal -> Maybe WebGPUDepthStencilState)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUDepthStencilState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUDepthStencilState
fromJSValUnchecked = WebGPUDepthStencilState -> JSM WebGPUDepthStencilState
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUDepthStencilState -> JSM WebGPUDepthStencilState)
-> (JSVal -> WebGPUDepthStencilState)
-> JSVal
-> JSM WebGPUDepthStencilState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUDepthStencilState
WebGPUDepthStencilState
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUDepthStencilState where
  makeObject :: WebGPUDepthStencilState -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUDepthStencilState -> JSVal)
-> WebGPUDepthStencilState
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUDepthStencilState -> JSVal
unWebGPUDepthStencilState

instance IsGObject WebGPUDepthStencilState where
  typeGType :: WebGPUDepthStencilState -> JSM GType
typeGType WebGPUDepthStencilState
_ = JSM GType
gTypeWebGPUDepthStencilState
  {-# INLINE typeGType #-}

noWebGPUDepthStencilState :: Maybe WebGPUDepthStencilState
noWebGPUDepthStencilState :: Maybe WebGPUDepthStencilState
noWebGPUDepthStencilState = Maybe WebGPUDepthStencilState
forall a. Maybe a
Nothing
{-# INLINE noWebGPUDepthStencilState #-}

gTypeWebGPUDepthStencilState :: JSM GType
gTypeWebGPUDepthStencilState :: JSM GType
gTypeWebGPUDepthStencilState = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUDepthStencilState"

-- | Functions for this inteface are in "JSDOM.WebGPUDrawable".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUDrawable Mozilla WebGPUDrawable documentation>
newtype WebGPUDrawable = WebGPUDrawable { WebGPUDrawable -> JSVal
unWebGPUDrawable :: JSVal }

instance PToJSVal WebGPUDrawable where
  pToJSVal :: WebGPUDrawable -> JSVal
pToJSVal = WebGPUDrawable -> JSVal
unWebGPUDrawable
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUDrawable where
  pFromJSVal :: JSVal -> WebGPUDrawable
pFromJSVal = JSVal -> WebGPUDrawable
WebGPUDrawable
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUDrawable where
  toJSVal :: WebGPUDrawable -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUDrawable -> JSVal) -> WebGPUDrawable -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUDrawable -> JSVal
unWebGPUDrawable
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUDrawable where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUDrawable)
fromJSVal JSVal
v = (JSVal -> WebGPUDrawable) -> Maybe JSVal -> Maybe WebGPUDrawable
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUDrawable
WebGPUDrawable (Maybe JSVal -> Maybe WebGPUDrawable)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUDrawable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUDrawable
fromJSValUnchecked = WebGPUDrawable -> JSM WebGPUDrawable
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUDrawable -> JSM WebGPUDrawable)
-> (JSVal -> WebGPUDrawable) -> JSVal -> JSM WebGPUDrawable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUDrawable
WebGPUDrawable
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUDrawable where
  makeObject :: WebGPUDrawable -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUDrawable -> JSVal) -> WebGPUDrawable -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUDrawable -> JSVal
unWebGPUDrawable

instance IsGObject WebGPUDrawable where
  typeGType :: WebGPUDrawable -> JSM GType
typeGType WebGPUDrawable
_ = JSM GType
gTypeWebGPUDrawable
  {-# INLINE typeGType #-}

noWebGPUDrawable :: Maybe WebGPUDrawable
noWebGPUDrawable :: Maybe WebGPUDrawable
noWebGPUDrawable = Maybe WebGPUDrawable
forall a. Maybe a
Nothing
{-# INLINE noWebGPUDrawable #-}

gTypeWebGPUDrawable :: JSM GType
gTypeWebGPUDrawable :: JSM GType
gTypeWebGPUDrawable = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUDrawable"

-- | Functions for this inteface are in "JSDOM.WebGPUFunction".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUFunction Mozilla WebGPUFunction documentation>
newtype WebGPUFunction = WebGPUFunction { WebGPUFunction -> JSVal
unWebGPUFunction :: JSVal }

instance PToJSVal WebGPUFunction where
  pToJSVal :: WebGPUFunction -> JSVal
pToJSVal = WebGPUFunction -> JSVal
unWebGPUFunction
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUFunction where
  pFromJSVal :: JSVal -> WebGPUFunction
pFromJSVal = JSVal -> WebGPUFunction
WebGPUFunction
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUFunction where
  toJSVal :: WebGPUFunction -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUFunction -> JSVal) -> WebGPUFunction -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUFunction -> JSVal
unWebGPUFunction
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUFunction where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUFunction)
fromJSVal JSVal
v = (JSVal -> WebGPUFunction) -> Maybe JSVal -> Maybe WebGPUFunction
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUFunction
WebGPUFunction (Maybe JSVal -> Maybe WebGPUFunction)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUFunction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUFunction
fromJSValUnchecked = WebGPUFunction -> JSM WebGPUFunction
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUFunction -> JSM WebGPUFunction)
-> (JSVal -> WebGPUFunction) -> JSVal -> JSM WebGPUFunction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUFunction
WebGPUFunction
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUFunction where
  makeObject :: WebGPUFunction -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUFunction -> JSVal) -> WebGPUFunction -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUFunction -> JSVal
unWebGPUFunction

instance IsGObject WebGPUFunction where
  typeGType :: WebGPUFunction -> JSM GType
typeGType WebGPUFunction
_ = JSM GType
gTypeWebGPUFunction
  {-# INLINE typeGType #-}

noWebGPUFunction :: Maybe WebGPUFunction
noWebGPUFunction :: Maybe WebGPUFunction
noWebGPUFunction = Maybe WebGPUFunction
forall a. Maybe a
Nothing
{-# INLINE noWebGPUFunction #-}

gTypeWebGPUFunction :: JSM GType
gTypeWebGPUFunction :: JSM GType
gTypeWebGPUFunction = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUFunction"

-- | Functions for this inteface are in "JSDOM.WebGPULibrary".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPULibrary Mozilla WebGPULibrary documentation>
newtype WebGPULibrary = WebGPULibrary { WebGPULibrary -> JSVal
unWebGPULibrary :: JSVal }

instance PToJSVal WebGPULibrary where
  pToJSVal :: WebGPULibrary -> JSVal
pToJSVal = WebGPULibrary -> JSVal
unWebGPULibrary
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPULibrary where
  pFromJSVal :: JSVal -> WebGPULibrary
pFromJSVal = JSVal -> WebGPULibrary
WebGPULibrary
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPULibrary where
  toJSVal :: WebGPULibrary -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPULibrary -> JSVal) -> WebGPULibrary -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPULibrary -> JSVal
unWebGPULibrary
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPULibrary where
  fromJSVal :: JSVal -> JSM (Maybe WebGPULibrary)
fromJSVal JSVal
v = (JSVal -> WebGPULibrary) -> Maybe JSVal -> Maybe WebGPULibrary
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPULibrary
WebGPULibrary (Maybe JSVal -> Maybe WebGPULibrary)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPULibrary)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPULibrary
fromJSValUnchecked = WebGPULibrary -> JSM WebGPULibrary
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPULibrary -> JSM WebGPULibrary)
-> (JSVal -> WebGPULibrary) -> JSVal -> JSM WebGPULibrary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPULibrary
WebGPULibrary
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPULibrary where
  makeObject :: WebGPULibrary -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPULibrary -> JSVal) -> WebGPULibrary -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPULibrary -> JSVal
unWebGPULibrary

instance IsGObject WebGPULibrary where
  typeGType :: WebGPULibrary -> JSM GType
typeGType WebGPULibrary
_ = JSM GType
gTypeWebGPULibrary
  {-# INLINE typeGType #-}

noWebGPULibrary :: Maybe WebGPULibrary
noWebGPULibrary :: Maybe WebGPULibrary
noWebGPULibrary = Maybe WebGPULibrary
forall a. Maybe a
Nothing
{-# INLINE noWebGPULibrary #-}

gTypeWebGPULibrary :: JSM GType
gTypeWebGPULibrary :: JSM GType
gTypeWebGPULibrary = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPULibrary"

-- | Functions for this inteface are in "JSDOM.WebGPURenderCommandEncoder".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPURenderCommandEncoder Mozilla WebGPURenderCommandEncoder documentation>
newtype WebGPURenderCommandEncoder = WebGPURenderCommandEncoder { WebGPURenderCommandEncoder -> JSVal
unWebGPURenderCommandEncoder :: JSVal }

instance PToJSVal WebGPURenderCommandEncoder where
  pToJSVal :: WebGPURenderCommandEncoder -> JSVal
pToJSVal = WebGPURenderCommandEncoder -> JSVal
unWebGPURenderCommandEncoder
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPURenderCommandEncoder where
  pFromJSVal :: JSVal -> WebGPURenderCommandEncoder
pFromJSVal = JSVal -> WebGPURenderCommandEncoder
WebGPURenderCommandEncoder
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPURenderCommandEncoder where
  toJSVal :: WebGPURenderCommandEncoder -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPURenderCommandEncoder -> JSVal)
-> WebGPURenderCommandEncoder
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderCommandEncoder -> JSVal
unWebGPURenderCommandEncoder
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPURenderCommandEncoder where
  fromJSVal :: JSVal -> JSM (Maybe WebGPURenderCommandEncoder)
fromJSVal JSVal
v = (JSVal -> WebGPURenderCommandEncoder)
-> Maybe JSVal -> Maybe WebGPURenderCommandEncoder
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPURenderCommandEncoder
WebGPURenderCommandEncoder (Maybe JSVal -> Maybe WebGPURenderCommandEncoder)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPURenderCommandEncoder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPURenderCommandEncoder
fromJSValUnchecked = WebGPURenderCommandEncoder -> JSM WebGPURenderCommandEncoder
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPURenderCommandEncoder -> JSM WebGPURenderCommandEncoder)
-> (JSVal -> WebGPURenderCommandEncoder)
-> JSVal
-> JSM WebGPURenderCommandEncoder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPURenderCommandEncoder
WebGPURenderCommandEncoder
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPURenderCommandEncoder where
  makeObject :: WebGPURenderCommandEncoder -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPURenderCommandEncoder -> JSVal)
-> WebGPURenderCommandEncoder
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderCommandEncoder -> JSVal
unWebGPURenderCommandEncoder

instance IsGObject WebGPURenderCommandEncoder where
  typeGType :: WebGPURenderCommandEncoder -> JSM GType
typeGType WebGPURenderCommandEncoder
_ = JSM GType
gTypeWebGPURenderCommandEncoder
  {-# INLINE typeGType #-}

noWebGPURenderCommandEncoder :: Maybe WebGPURenderCommandEncoder
noWebGPURenderCommandEncoder :: Maybe WebGPURenderCommandEncoder
noWebGPURenderCommandEncoder = Maybe WebGPURenderCommandEncoder
forall a. Maybe a
Nothing
{-# INLINE noWebGPURenderCommandEncoder #-}

gTypeWebGPURenderCommandEncoder :: JSM GType
gTypeWebGPURenderCommandEncoder :: JSM GType
gTypeWebGPURenderCommandEncoder = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPURenderCommandEncoder"

-- | Functions for this inteface are in "JSDOM.WebGPURenderPassAttachmentDescriptor".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPURenderPassAttachmentDescriptor Mozilla WebGPURenderPassAttachmentDescriptor documentation>
newtype WebGPURenderPassAttachmentDescriptor = WebGPURenderPassAttachmentDescriptor { WebGPURenderPassAttachmentDescriptor -> JSVal
unWebGPURenderPassAttachmentDescriptor :: JSVal }

instance PToJSVal WebGPURenderPassAttachmentDescriptor where
  pToJSVal :: WebGPURenderPassAttachmentDescriptor -> JSVal
pToJSVal = WebGPURenderPassAttachmentDescriptor -> JSVal
unWebGPURenderPassAttachmentDescriptor
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPURenderPassAttachmentDescriptor where
  pFromJSVal :: JSVal -> WebGPURenderPassAttachmentDescriptor
pFromJSVal = JSVal -> WebGPURenderPassAttachmentDescriptor
WebGPURenderPassAttachmentDescriptor
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPURenderPassAttachmentDescriptor where
  toJSVal :: WebGPURenderPassAttachmentDescriptor -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPURenderPassAttachmentDescriptor -> JSVal)
-> WebGPURenderPassAttachmentDescriptor
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPassAttachmentDescriptor -> JSVal
unWebGPURenderPassAttachmentDescriptor
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPURenderPassAttachmentDescriptor where
  fromJSVal :: JSVal -> JSM (Maybe WebGPURenderPassAttachmentDescriptor)
fromJSVal JSVal
v = (JSVal -> WebGPURenderPassAttachmentDescriptor)
-> Maybe JSVal -> Maybe WebGPURenderPassAttachmentDescriptor
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPURenderPassAttachmentDescriptor
WebGPURenderPassAttachmentDescriptor (Maybe JSVal -> Maybe WebGPURenderPassAttachmentDescriptor)
-> JSM (Maybe JSVal)
-> JSM (Maybe WebGPURenderPassAttachmentDescriptor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPURenderPassAttachmentDescriptor
fromJSValUnchecked = WebGPURenderPassAttachmentDescriptor
-> JSM WebGPURenderPassAttachmentDescriptor
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPURenderPassAttachmentDescriptor
 -> JSM WebGPURenderPassAttachmentDescriptor)
-> (JSVal -> WebGPURenderPassAttachmentDescriptor)
-> JSVal
-> JSM WebGPURenderPassAttachmentDescriptor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPURenderPassAttachmentDescriptor
WebGPURenderPassAttachmentDescriptor
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPURenderPassAttachmentDescriptor where
  makeObject :: WebGPURenderPassAttachmentDescriptor -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPURenderPassAttachmentDescriptor -> JSVal)
-> WebGPURenderPassAttachmentDescriptor
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPassAttachmentDescriptor -> JSVal
unWebGPURenderPassAttachmentDescriptor

class (IsGObject o) => IsWebGPURenderPassAttachmentDescriptor o
toWebGPURenderPassAttachmentDescriptor :: IsWebGPURenderPassAttachmentDescriptor o => o -> WebGPURenderPassAttachmentDescriptor
toWebGPURenderPassAttachmentDescriptor :: forall o.
IsWebGPURenderPassAttachmentDescriptor o =>
o -> WebGPURenderPassAttachmentDescriptor
toWebGPURenderPassAttachmentDescriptor = JSVal -> WebGPURenderPassAttachmentDescriptor
WebGPURenderPassAttachmentDescriptor (JSVal -> WebGPURenderPassAttachmentDescriptor)
-> (o -> JSVal) -> o -> WebGPURenderPassAttachmentDescriptor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsWebGPURenderPassAttachmentDescriptor WebGPURenderPassAttachmentDescriptor
instance IsGObject WebGPURenderPassAttachmentDescriptor where
  typeGType :: WebGPURenderPassAttachmentDescriptor -> JSM GType
typeGType WebGPURenderPassAttachmentDescriptor
_ = JSM GType
gTypeWebGPURenderPassAttachmentDescriptor
  {-# INLINE typeGType #-}

noWebGPURenderPassAttachmentDescriptor :: Maybe WebGPURenderPassAttachmentDescriptor
noWebGPURenderPassAttachmentDescriptor :: Maybe WebGPURenderPassAttachmentDescriptor
noWebGPURenderPassAttachmentDescriptor = Maybe WebGPURenderPassAttachmentDescriptor
forall a. Maybe a
Nothing
{-# INLINE noWebGPURenderPassAttachmentDescriptor #-}

gTypeWebGPURenderPassAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPassAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPassAttachmentDescriptor = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPURenderPassAttachmentDescriptor"

-- | Functions for this inteface are in "JSDOM.WebGPURenderPassColorAttachmentDescriptor".
-- Base interface functions are in:
--
--     * "JSDOM.WebGPURenderPassAttachmentDescriptor"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPURenderPassColorAttachmentDescriptor Mozilla WebGPURenderPassColorAttachmentDescriptor documentation>
newtype WebGPURenderPassColorAttachmentDescriptor = WebGPURenderPassColorAttachmentDescriptor { WebGPURenderPassColorAttachmentDescriptor -> JSVal
unWebGPURenderPassColorAttachmentDescriptor :: JSVal }

instance PToJSVal WebGPURenderPassColorAttachmentDescriptor where
  pToJSVal :: WebGPURenderPassColorAttachmentDescriptor -> JSVal
pToJSVal = WebGPURenderPassColorAttachmentDescriptor -> JSVal
unWebGPURenderPassColorAttachmentDescriptor
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPURenderPassColorAttachmentDescriptor where
  pFromJSVal :: JSVal -> WebGPURenderPassColorAttachmentDescriptor
pFromJSVal = JSVal -> WebGPURenderPassColorAttachmentDescriptor
WebGPURenderPassColorAttachmentDescriptor
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPURenderPassColorAttachmentDescriptor where
  toJSVal :: WebGPURenderPassColorAttachmentDescriptor -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPURenderPassColorAttachmentDescriptor -> JSVal)
-> WebGPURenderPassColorAttachmentDescriptor
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPassColorAttachmentDescriptor -> JSVal
unWebGPURenderPassColorAttachmentDescriptor
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPURenderPassColorAttachmentDescriptor where
  fromJSVal :: JSVal -> JSM (Maybe WebGPURenderPassColorAttachmentDescriptor)
fromJSVal JSVal
v = (JSVal -> WebGPURenderPassColorAttachmentDescriptor)
-> Maybe JSVal -> Maybe WebGPURenderPassColorAttachmentDescriptor
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPURenderPassColorAttachmentDescriptor
WebGPURenderPassColorAttachmentDescriptor (Maybe JSVal -> Maybe WebGPURenderPassColorAttachmentDescriptor)
-> JSM (Maybe JSVal)
-> JSM (Maybe WebGPURenderPassColorAttachmentDescriptor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPURenderPassColorAttachmentDescriptor
fromJSValUnchecked = WebGPURenderPassColorAttachmentDescriptor
-> JSM WebGPURenderPassColorAttachmentDescriptor
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPURenderPassColorAttachmentDescriptor
 -> JSM WebGPURenderPassColorAttachmentDescriptor)
-> (JSVal -> WebGPURenderPassColorAttachmentDescriptor)
-> JSVal
-> JSM WebGPURenderPassColorAttachmentDescriptor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPURenderPassColorAttachmentDescriptor
WebGPURenderPassColorAttachmentDescriptor
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPURenderPassColorAttachmentDescriptor where
  makeObject :: WebGPURenderPassColorAttachmentDescriptor -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPURenderPassColorAttachmentDescriptor -> JSVal)
-> WebGPURenderPassColorAttachmentDescriptor
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPassColorAttachmentDescriptor -> JSVal
unWebGPURenderPassColorAttachmentDescriptor

instance IsWebGPURenderPassAttachmentDescriptor WebGPURenderPassColorAttachmentDescriptor
instance IsGObject WebGPURenderPassColorAttachmentDescriptor where
  typeGType :: WebGPURenderPassColorAttachmentDescriptor -> JSM GType
typeGType WebGPURenderPassColorAttachmentDescriptor
_ = JSM GType
gTypeWebGPURenderPassColorAttachmentDescriptor
  {-# INLINE typeGType #-}

noWebGPURenderPassColorAttachmentDescriptor :: Maybe WebGPURenderPassColorAttachmentDescriptor
noWebGPURenderPassColorAttachmentDescriptor :: Maybe WebGPURenderPassColorAttachmentDescriptor
noWebGPURenderPassColorAttachmentDescriptor = Maybe WebGPURenderPassColorAttachmentDescriptor
forall a. Maybe a
Nothing
{-# INLINE noWebGPURenderPassColorAttachmentDescriptor #-}

gTypeWebGPURenderPassColorAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPassColorAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPassColorAttachmentDescriptor = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPURenderPassColorAttachmentDescriptor"

-- | Functions for this inteface are in "JSDOM.WebGPURenderPassDepthAttachmentDescriptor".
-- Base interface functions are in:
--
--     * "JSDOM.WebGPURenderPassAttachmentDescriptor"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPURenderPassDepthAttachmentDescriptor Mozilla WebGPURenderPassDepthAttachmentDescriptor documentation>
newtype WebGPURenderPassDepthAttachmentDescriptor = WebGPURenderPassDepthAttachmentDescriptor { WebGPURenderPassDepthAttachmentDescriptor -> JSVal
unWebGPURenderPassDepthAttachmentDescriptor :: JSVal }

instance PToJSVal WebGPURenderPassDepthAttachmentDescriptor where
  pToJSVal :: WebGPURenderPassDepthAttachmentDescriptor -> JSVal
pToJSVal = WebGPURenderPassDepthAttachmentDescriptor -> JSVal
unWebGPURenderPassDepthAttachmentDescriptor
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPURenderPassDepthAttachmentDescriptor where
  pFromJSVal :: JSVal -> WebGPURenderPassDepthAttachmentDescriptor
pFromJSVal = JSVal -> WebGPURenderPassDepthAttachmentDescriptor
WebGPURenderPassDepthAttachmentDescriptor
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPURenderPassDepthAttachmentDescriptor where
  toJSVal :: WebGPURenderPassDepthAttachmentDescriptor -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPURenderPassDepthAttachmentDescriptor -> JSVal)
-> WebGPURenderPassDepthAttachmentDescriptor
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPassDepthAttachmentDescriptor -> JSVal
unWebGPURenderPassDepthAttachmentDescriptor
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPURenderPassDepthAttachmentDescriptor where
  fromJSVal :: JSVal -> JSM (Maybe WebGPURenderPassDepthAttachmentDescriptor)
fromJSVal JSVal
v = (JSVal -> WebGPURenderPassDepthAttachmentDescriptor)
-> Maybe JSVal -> Maybe WebGPURenderPassDepthAttachmentDescriptor
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPURenderPassDepthAttachmentDescriptor
WebGPURenderPassDepthAttachmentDescriptor (Maybe JSVal -> Maybe WebGPURenderPassDepthAttachmentDescriptor)
-> JSM (Maybe JSVal)
-> JSM (Maybe WebGPURenderPassDepthAttachmentDescriptor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPURenderPassDepthAttachmentDescriptor
fromJSValUnchecked = WebGPURenderPassDepthAttachmentDescriptor
-> JSM WebGPURenderPassDepthAttachmentDescriptor
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPURenderPassDepthAttachmentDescriptor
 -> JSM WebGPURenderPassDepthAttachmentDescriptor)
-> (JSVal -> WebGPURenderPassDepthAttachmentDescriptor)
-> JSVal
-> JSM WebGPURenderPassDepthAttachmentDescriptor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPURenderPassDepthAttachmentDescriptor
WebGPURenderPassDepthAttachmentDescriptor
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPURenderPassDepthAttachmentDescriptor where
  makeObject :: WebGPURenderPassDepthAttachmentDescriptor -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPURenderPassDepthAttachmentDescriptor -> JSVal)
-> WebGPURenderPassDepthAttachmentDescriptor
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPassDepthAttachmentDescriptor -> JSVal
unWebGPURenderPassDepthAttachmentDescriptor

instance IsWebGPURenderPassAttachmentDescriptor WebGPURenderPassDepthAttachmentDescriptor
instance IsGObject WebGPURenderPassDepthAttachmentDescriptor where
  typeGType :: WebGPURenderPassDepthAttachmentDescriptor -> JSM GType
typeGType WebGPURenderPassDepthAttachmentDescriptor
_ = JSM GType
gTypeWebGPURenderPassDepthAttachmentDescriptor
  {-# INLINE typeGType #-}

noWebGPURenderPassDepthAttachmentDescriptor :: Maybe WebGPURenderPassDepthAttachmentDescriptor
noWebGPURenderPassDepthAttachmentDescriptor :: Maybe WebGPURenderPassDepthAttachmentDescriptor
noWebGPURenderPassDepthAttachmentDescriptor = Maybe WebGPURenderPassDepthAttachmentDescriptor
forall a. Maybe a
Nothing
{-# INLINE noWebGPURenderPassDepthAttachmentDescriptor #-}

gTypeWebGPURenderPassDepthAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPassDepthAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPassDepthAttachmentDescriptor = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPURenderPassDepthAttachmentDescriptor"

-- | Functions for this inteface are in "JSDOM.WebGPURenderPassDescriptor".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPURenderPassDescriptor Mozilla WebGPURenderPassDescriptor documentation>
newtype WebGPURenderPassDescriptor = WebGPURenderPassDescriptor { WebGPURenderPassDescriptor -> JSVal
unWebGPURenderPassDescriptor :: JSVal }

instance PToJSVal WebGPURenderPassDescriptor where
  pToJSVal :: WebGPURenderPassDescriptor -> JSVal
pToJSVal = WebGPURenderPassDescriptor -> JSVal
unWebGPURenderPassDescriptor
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPURenderPassDescriptor where
  pFromJSVal :: JSVal -> WebGPURenderPassDescriptor
pFromJSVal = JSVal -> WebGPURenderPassDescriptor
WebGPURenderPassDescriptor
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPURenderPassDescriptor where
  toJSVal :: WebGPURenderPassDescriptor -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPURenderPassDescriptor -> JSVal)
-> WebGPURenderPassDescriptor
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPassDescriptor -> JSVal
unWebGPURenderPassDescriptor
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPURenderPassDescriptor where
  fromJSVal :: JSVal -> JSM (Maybe WebGPURenderPassDescriptor)
fromJSVal JSVal
v = (JSVal -> WebGPURenderPassDescriptor)
-> Maybe JSVal -> Maybe WebGPURenderPassDescriptor
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPURenderPassDescriptor
WebGPURenderPassDescriptor (Maybe JSVal -> Maybe WebGPURenderPassDescriptor)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPURenderPassDescriptor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPURenderPassDescriptor
fromJSValUnchecked = WebGPURenderPassDescriptor -> JSM WebGPURenderPassDescriptor
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPURenderPassDescriptor -> JSM WebGPURenderPassDescriptor)
-> (JSVal -> WebGPURenderPassDescriptor)
-> JSVal
-> JSM WebGPURenderPassDescriptor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPURenderPassDescriptor
WebGPURenderPassDescriptor
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPURenderPassDescriptor where
  makeObject :: WebGPURenderPassDescriptor -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPURenderPassDescriptor -> JSVal)
-> WebGPURenderPassDescriptor
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPassDescriptor -> JSVal
unWebGPURenderPassDescriptor

instance IsGObject WebGPURenderPassDescriptor where
  typeGType :: WebGPURenderPassDescriptor -> JSM GType
typeGType WebGPURenderPassDescriptor
_ = JSM GType
gTypeWebGPURenderPassDescriptor
  {-# INLINE typeGType #-}

noWebGPURenderPassDescriptor :: Maybe WebGPURenderPassDescriptor
noWebGPURenderPassDescriptor :: Maybe WebGPURenderPassDescriptor
noWebGPURenderPassDescriptor = Maybe WebGPURenderPassDescriptor
forall a. Maybe a
Nothing
{-# INLINE noWebGPURenderPassDescriptor #-}

gTypeWebGPURenderPassDescriptor :: JSM GType
gTypeWebGPURenderPassDescriptor :: JSM GType
gTypeWebGPURenderPassDescriptor = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPURenderPassDescriptor"

-- | Functions for this inteface are in "JSDOM.WebGPURenderPipelineColorAttachmentDescriptor".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPURenderPipelineColorAttachmentDescriptor Mozilla WebGPURenderPipelineColorAttachmentDescriptor documentation>
newtype WebGPURenderPipelineColorAttachmentDescriptor = WebGPURenderPipelineColorAttachmentDescriptor { WebGPURenderPipelineColorAttachmentDescriptor -> JSVal
unWebGPURenderPipelineColorAttachmentDescriptor :: JSVal }

instance PToJSVal WebGPURenderPipelineColorAttachmentDescriptor where
  pToJSVal :: WebGPURenderPipelineColorAttachmentDescriptor -> JSVal
pToJSVal = WebGPURenderPipelineColorAttachmentDescriptor -> JSVal
unWebGPURenderPipelineColorAttachmentDescriptor
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPURenderPipelineColorAttachmentDescriptor where
  pFromJSVal :: JSVal -> WebGPURenderPipelineColorAttachmentDescriptor
pFromJSVal = JSVal -> WebGPURenderPipelineColorAttachmentDescriptor
WebGPURenderPipelineColorAttachmentDescriptor
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPURenderPipelineColorAttachmentDescriptor where
  toJSVal :: WebGPURenderPipelineColorAttachmentDescriptor -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPURenderPipelineColorAttachmentDescriptor -> JSVal)
-> WebGPURenderPipelineColorAttachmentDescriptor
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPipelineColorAttachmentDescriptor -> JSVal
unWebGPURenderPipelineColorAttachmentDescriptor
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPURenderPipelineColorAttachmentDescriptor where
  fromJSVal :: JSVal -> JSM (Maybe WebGPURenderPipelineColorAttachmentDescriptor)
fromJSVal JSVal
v = (JSVal -> WebGPURenderPipelineColorAttachmentDescriptor)
-> Maybe JSVal
-> Maybe WebGPURenderPipelineColorAttachmentDescriptor
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPURenderPipelineColorAttachmentDescriptor
WebGPURenderPipelineColorAttachmentDescriptor (Maybe JSVal
 -> Maybe WebGPURenderPipelineColorAttachmentDescriptor)
-> JSM (Maybe JSVal)
-> JSM (Maybe WebGPURenderPipelineColorAttachmentDescriptor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPURenderPipelineColorAttachmentDescriptor
fromJSValUnchecked = WebGPURenderPipelineColorAttachmentDescriptor
-> JSM WebGPURenderPipelineColorAttachmentDescriptor
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPURenderPipelineColorAttachmentDescriptor
 -> JSM WebGPURenderPipelineColorAttachmentDescriptor)
-> (JSVal -> WebGPURenderPipelineColorAttachmentDescriptor)
-> JSVal
-> JSM WebGPURenderPipelineColorAttachmentDescriptor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPURenderPipelineColorAttachmentDescriptor
WebGPURenderPipelineColorAttachmentDescriptor
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPURenderPipelineColorAttachmentDescriptor where
  makeObject :: WebGPURenderPipelineColorAttachmentDescriptor -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPURenderPipelineColorAttachmentDescriptor -> JSVal)
-> WebGPURenderPipelineColorAttachmentDescriptor
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPipelineColorAttachmentDescriptor -> JSVal
unWebGPURenderPipelineColorAttachmentDescriptor

instance IsGObject WebGPURenderPipelineColorAttachmentDescriptor where
  typeGType :: WebGPURenderPipelineColorAttachmentDescriptor -> JSM GType
typeGType WebGPURenderPipelineColorAttachmentDescriptor
_ = JSM GType
gTypeWebGPURenderPipelineColorAttachmentDescriptor
  {-# INLINE typeGType #-}

noWebGPURenderPipelineColorAttachmentDescriptor :: Maybe WebGPURenderPipelineColorAttachmentDescriptor
noWebGPURenderPipelineColorAttachmentDescriptor :: Maybe WebGPURenderPipelineColorAttachmentDescriptor
noWebGPURenderPipelineColorAttachmentDescriptor = Maybe WebGPURenderPipelineColorAttachmentDescriptor
forall a. Maybe a
Nothing
{-# INLINE noWebGPURenderPipelineColorAttachmentDescriptor #-}

gTypeWebGPURenderPipelineColorAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPipelineColorAttachmentDescriptor :: JSM GType
gTypeWebGPURenderPipelineColorAttachmentDescriptor = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPURenderPipelineColorAttachmentDescriptor"

-- | Functions for this inteface are in "JSDOM.WebGPURenderPipelineDescriptor".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPURenderPipelineDescriptor Mozilla WebGPURenderPipelineDescriptor documentation>
newtype WebGPURenderPipelineDescriptor = WebGPURenderPipelineDescriptor { WebGPURenderPipelineDescriptor -> JSVal
unWebGPURenderPipelineDescriptor :: JSVal }

instance PToJSVal WebGPURenderPipelineDescriptor where
  pToJSVal :: WebGPURenderPipelineDescriptor -> JSVal
pToJSVal = WebGPURenderPipelineDescriptor -> JSVal
unWebGPURenderPipelineDescriptor
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPURenderPipelineDescriptor where
  pFromJSVal :: JSVal -> WebGPURenderPipelineDescriptor
pFromJSVal = JSVal -> WebGPURenderPipelineDescriptor
WebGPURenderPipelineDescriptor
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPURenderPipelineDescriptor where
  toJSVal :: WebGPURenderPipelineDescriptor -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPURenderPipelineDescriptor -> JSVal)
-> WebGPURenderPipelineDescriptor
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPipelineDescriptor -> JSVal
unWebGPURenderPipelineDescriptor
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPURenderPipelineDescriptor where
  fromJSVal :: JSVal -> JSM (Maybe WebGPURenderPipelineDescriptor)
fromJSVal JSVal
v = (JSVal -> WebGPURenderPipelineDescriptor)
-> Maybe JSVal -> Maybe WebGPURenderPipelineDescriptor
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPURenderPipelineDescriptor
WebGPURenderPipelineDescriptor (Maybe JSVal -> Maybe WebGPURenderPipelineDescriptor)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPURenderPipelineDescriptor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPURenderPipelineDescriptor
fromJSValUnchecked = WebGPURenderPipelineDescriptor
-> JSM WebGPURenderPipelineDescriptor
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPURenderPipelineDescriptor
 -> JSM WebGPURenderPipelineDescriptor)
-> (JSVal -> WebGPURenderPipelineDescriptor)
-> JSVal
-> JSM WebGPURenderPipelineDescriptor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPURenderPipelineDescriptor
WebGPURenderPipelineDescriptor
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPURenderPipelineDescriptor where
  makeObject :: WebGPURenderPipelineDescriptor -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPURenderPipelineDescriptor -> JSVal)
-> WebGPURenderPipelineDescriptor
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPipelineDescriptor -> JSVal
unWebGPURenderPipelineDescriptor

instance IsGObject WebGPURenderPipelineDescriptor where
  typeGType :: WebGPURenderPipelineDescriptor -> JSM GType
typeGType WebGPURenderPipelineDescriptor
_ = JSM GType
gTypeWebGPURenderPipelineDescriptor
  {-# INLINE typeGType #-}

noWebGPURenderPipelineDescriptor :: Maybe WebGPURenderPipelineDescriptor
noWebGPURenderPipelineDescriptor :: Maybe WebGPURenderPipelineDescriptor
noWebGPURenderPipelineDescriptor = Maybe WebGPURenderPipelineDescriptor
forall a. Maybe a
Nothing
{-# INLINE noWebGPURenderPipelineDescriptor #-}

gTypeWebGPURenderPipelineDescriptor :: JSM GType
gTypeWebGPURenderPipelineDescriptor :: JSM GType
gTypeWebGPURenderPipelineDescriptor = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPURenderPipelineDescriptor"

-- | Functions for this inteface are in "JSDOM.WebGPURenderPipelineState".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPURenderPipelineState Mozilla WebGPURenderPipelineState documentation>
newtype WebGPURenderPipelineState = WebGPURenderPipelineState { WebGPURenderPipelineState -> JSVal
unWebGPURenderPipelineState :: JSVal }

instance PToJSVal WebGPURenderPipelineState where
  pToJSVal :: WebGPURenderPipelineState -> JSVal
pToJSVal = WebGPURenderPipelineState -> JSVal
unWebGPURenderPipelineState
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPURenderPipelineState where
  pFromJSVal :: JSVal -> WebGPURenderPipelineState
pFromJSVal = JSVal -> WebGPURenderPipelineState
WebGPURenderPipelineState
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPURenderPipelineState where
  toJSVal :: WebGPURenderPipelineState -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPURenderPipelineState -> JSVal)
-> WebGPURenderPipelineState
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPipelineState -> JSVal
unWebGPURenderPipelineState
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPURenderPipelineState where
  fromJSVal :: JSVal -> JSM (Maybe WebGPURenderPipelineState)
fromJSVal JSVal
v = (JSVal -> WebGPURenderPipelineState)
-> Maybe JSVal -> Maybe WebGPURenderPipelineState
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPURenderPipelineState
WebGPURenderPipelineState (Maybe JSVal -> Maybe WebGPURenderPipelineState)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPURenderPipelineState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPURenderPipelineState
fromJSValUnchecked = WebGPURenderPipelineState -> JSM WebGPURenderPipelineState
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPURenderPipelineState -> JSM WebGPURenderPipelineState)
-> (JSVal -> WebGPURenderPipelineState)
-> JSVal
-> JSM WebGPURenderPipelineState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPURenderPipelineState
WebGPURenderPipelineState
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPURenderPipelineState where
  makeObject :: WebGPURenderPipelineState -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPURenderPipelineState -> JSVal)
-> WebGPURenderPipelineState
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderPipelineState -> JSVal
unWebGPURenderPipelineState

instance IsGObject WebGPURenderPipelineState where
  typeGType :: WebGPURenderPipelineState -> JSM GType
typeGType WebGPURenderPipelineState
_ = JSM GType
gTypeWebGPURenderPipelineState
  {-# INLINE typeGType #-}

noWebGPURenderPipelineState :: Maybe WebGPURenderPipelineState
noWebGPURenderPipelineState :: Maybe WebGPURenderPipelineState
noWebGPURenderPipelineState = Maybe WebGPURenderPipelineState
forall a. Maybe a
Nothing
{-# INLINE noWebGPURenderPipelineState #-}

gTypeWebGPURenderPipelineState :: JSM GType
gTypeWebGPURenderPipelineState :: JSM GType
gTypeWebGPURenderPipelineState = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPURenderPipelineState"

-- | Functions for this inteface are in "JSDOM.WebGPURenderingContext".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPURenderingContext Mozilla WebGPURenderingContext documentation>
newtype WebGPURenderingContext = WebGPURenderingContext { WebGPURenderingContext -> JSVal
unWebGPURenderingContext :: JSVal }

instance PToJSVal WebGPURenderingContext where
  pToJSVal :: WebGPURenderingContext -> JSVal
pToJSVal = WebGPURenderingContext -> JSVal
unWebGPURenderingContext
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPURenderingContext where
  pFromJSVal :: JSVal -> WebGPURenderingContext
pFromJSVal = JSVal -> WebGPURenderingContext
WebGPURenderingContext
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPURenderingContext where
  toJSVal :: WebGPURenderingContext -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPURenderingContext -> JSVal)
-> WebGPURenderingContext
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderingContext -> JSVal
unWebGPURenderingContext
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPURenderingContext where
  fromJSVal :: JSVal -> JSM (Maybe WebGPURenderingContext)
fromJSVal JSVal
v = (JSVal -> WebGPURenderingContext)
-> Maybe JSVal -> Maybe WebGPURenderingContext
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPURenderingContext
WebGPURenderingContext (Maybe JSVal -> Maybe WebGPURenderingContext)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPURenderingContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPURenderingContext
fromJSValUnchecked = WebGPURenderingContext -> JSM WebGPURenderingContext
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPURenderingContext -> JSM WebGPURenderingContext)
-> (JSVal -> WebGPURenderingContext)
-> JSVal
-> JSM WebGPURenderingContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPURenderingContext
WebGPURenderingContext
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPURenderingContext where
  makeObject :: WebGPURenderingContext -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPURenderingContext -> JSVal)
-> WebGPURenderingContext
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPURenderingContext -> JSVal
unWebGPURenderingContext

instance IsGObject WebGPURenderingContext where
  typeGType :: WebGPURenderingContext -> JSM GType
typeGType WebGPURenderingContext
_ = JSM GType
gTypeWebGPURenderingContext
  {-# INLINE typeGType #-}

noWebGPURenderingContext :: Maybe WebGPURenderingContext
noWebGPURenderingContext :: Maybe WebGPURenderingContext
noWebGPURenderingContext = Maybe WebGPURenderingContext
forall a. Maybe a
Nothing
{-# INLINE noWebGPURenderingContext #-}

gTypeWebGPURenderingContext :: JSM GType
gTypeWebGPURenderingContext :: JSM GType
gTypeWebGPURenderingContext = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPURenderingContext"

-- | Functions for this inteface are in "JSDOM.WebGPUSize".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUSize Mozilla WebGPUSize documentation>
newtype WebGPUSize = WebGPUSize { WebGPUSize -> JSVal
unWebGPUSize :: JSVal }

instance PToJSVal WebGPUSize where
  pToJSVal :: WebGPUSize -> JSVal
pToJSVal = WebGPUSize -> JSVal
unWebGPUSize
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUSize where
  pFromJSVal :: JSVal -> WebGPUSize
pFromJSVal = JSVal -> WebGPUSize
WebGPUSize
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUSize where
  toJSVal :: WebGPUSize -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUSize -> JSVal) -> WebGPUSize -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUSize -> JSVal
unWebGPUSize
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUSize where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUSize)
fromJSVal JSVal
v = (JSVal -> WebGPUSize) -> Maybe JSVal -> Maybe WebGPUSize
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUSize
WebGPUSize (Maybe JSVal -> Maybe WebGPUSize)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUSize)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUSize
fromJSValUnchecked = WebGPUSize -> JSM WebGPUSize
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUSize -> JSM WebGPUSize)
-> (JSVal -> WebGPUSize) -> JSVal -> JSM WebGPUSize
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUSize
WebGPUSize
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUSize where
  makeObject :: WebGPUSize -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUSize -> JSVal) -> WebGPUSize -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUSize -> JSVal
unWebGPUSize

instance IsGObject WebGPUSize where
  typeGType :: WebGPUSize -> JSM GType
typeGType WebGPUSize
_ = JSM GType
gTypeWebGPUSize
  {-# INLINE typeGType #-}

noWebGPUSize :: Maybe WebGPUSize
noWebGPUSize :: Maybe WebGPUSize
noWebGPUSize = Maybe WebGPUSize
forall a. Maybe a
Nothing
{-# INLINE noWebGPUSize #-}

gTypeWebGPUSize :: JSM GType
gTypeWebGPUSize :: JSM GType
gTypeWebGPUSize = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUSize"

-- | Functions for this inteface are in "JSDOM.WebGPUTexture".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUTexture Mozilla WebGPUTexture documentation>
newtype WebGPUTexture = WebGPUTexture { WebGPUTexture -> JSVal
unWebGPUTexture :: JSVal }

instance PToJSVal WebGPUTexture where
  pToJSVal :: WebGPUTexture -> JSVal
pToJSVal = WebGPUTexture -> JSVal
unWebGPUTexture
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUTexture where
  pFromJSVal :: JSVal -> WebGPUTexture
pFromJSVal = JSVal -> WebGPUTexture
WebGPUTexture
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUTexture where
  toJSVal :: WebGPUTexture -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUTexture -> JSVal) -> WebGPUTexture -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUTexture -> JSVal
unWebGPUTexture
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUTexture where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUTexture)
fromJSVal JSVal
v = (JSVal -> WebGPUTexture) -> Maybe JSVal -> Maybe WebGPUTexture
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUTexture
WebGPUTexture (Maybe JSVal -> Maybe WebGPUTexture)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUTexture)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUTexture
fromJSValUnchecked = WebGPUTexture -> JSM WebGPUTexture
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUTexture -> JSM WebGPUTexture)
-> (JSVal -> WebGPUTexture) -> JSVal -> JSM WebGPUTexture
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUTexture
WebGPUTexture
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUTexture where
  makeObject :: WebGPUTexture -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUTexture -> JSVal) -> WebGPUTexture -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUTexture -> JSVal
unWebGPUTexture

instance IsGObject WebGPUTexture where
  typeGType :: WebGPUTexture -> JSM GType
typeGType WebGPUTexture
_ = JSM GType
gTypeWebGPUTexture
  {-# INLINE typeGType #-}

noWebGPUTexture :: Maybe WebGPUTexture
noWebGPUTexture :: Maybe WebGPUTexture
noWebGPUTexture = Maybe WebGPUTexture
forall a. Maybe a
Nothing
{-# INLINE noWebGPUTexture #-}

gTypeWebGPUTexture :: JSM GType
gTypeWebGPUTexture :: JSM GType
gTypeWebGPUTexture = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUTexture"

-- | Functions for this inteface are in "JSDOM.WebGPUTextureDescriptor".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebGPUTextureDescriptor Mozilla WebGPUTextureDescriptor documentation>
newtype WebGPUTextureDescriptor = WebGPUTextureDescriptor { WebGPUTextureDescriptor -> JSVal
unWebGPUTextureDescriptor :: JSVal }

instance PToJSVal WebGPUTextureDescriptor where
  pToJSVal :: WebGPUTextureDescriptor -> JSVal
pToJSVal = WebGPUTextureDescriptor -> JSVal
unWebGPUTextureDescriptor
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebGPUTextureDescriptor where
  pFromJSVal :: JSVal -> WebGPUTextureDescriptor
pFromJSVal = JSVal -> WebGPUTextureDescriptor
WebGPUTextureDescriptor
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebGPUTextureDescriptor where
  toJSVal :: WebGPUTextureDescriptor -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebGPUTextureDescriptor -> JSVal)
-> WebGPUTextureDescriptor
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUTextureDescriptor -> JSVal
unWebGPUTextureDescriptor
  {-# INLINE toJSVal #-}

instance FromJSVal WebGPUTextureDescriptor where
  fromJSVal :: JSVal -> JSM (Maybe WebGPUTextureDescriptor)
fromJSVal JSVal
v = (JSVal -> WebGPUTextureDescriptor)
-> Maybe JSVal -> Maybe WebGPUTextureDescriptor
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebGPUTextureDescriptor
WebGPUTextureDescriptor (Maybe JSVal -> Maybe WebGPUTextureDescriptor)
-> JSM (Maybe JSVal) -> JSM (Maybe WebGPUTextureDescriptor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebGPUTextureDescriptor
fromJSValUnchecked = WebGPUTextureDescriptor -> JSM WebGPUTextureDescriptor
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUTextureDescriptor -> JSM WebGPUTextureDescriptor)
-> (JSVal -> WebGPUTextureDescriptor)
-> JSVal
-> JSM WebGPUTextureDescriptor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebGPUTextureDescriptor
WebGPUTextureDescriptor
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebGPUTextureDescriptor where
  makeObject :: WebGPUTextureDescriptor -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebGPUTextureDescriptor -> JSVal)
-> WebGPUTextureDescriptor
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebGPUTextureDescriptor -> JSVal
unWebGPUTextureDescriptor

instance IsGObject WebGPUTextureDescriptor where
  typeGType :: WebGPUTextureDescriptor -> JSM GType
typeGType WebGPUTextureDescriptor
_ = JSM GType
gTypeWebGPUTextureDescriptor
  {-# INLINE typeGType #-}

noWebGPUTextureDescriptor :: Maybe WebGPUTextureDescriptor
noWebGPUTextureDescriptor :: Maybe WebGPUTextureDescriptor
noWebGPUTextureDescriptor = Maybe WebGPUTextureDescriptor
forall a. Maybe a
Nothing
{-# INLINE noWebGPUTextureDescriptor #-}

gTypeWebGPUTextureDescriptor :: JSM GType
gTypeWebGPUTextureDescriptor :: JSM GType
gTypeWebGPUTextureDescriptor = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebGPUTextureDescriptor"

-- | Functions for this inteface are in "JSDOM.WebKitAnimationEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitAnimationEvent Mozilla WebKitAnimationEvent documentation>
newtype WebKitAnimationEvent = WebKitAnimationEvent { WebKitAnimationEvent -> JSVal
unWebKitAnimationEvent :: JSVal }

instance PToJSVal WebKitAnimationEvent where
  pToJSVal :: WebKitAnimationEvent -> JSVal
pToJSVal = WebKitAnimationEvent -> JSVal
unWebKitAnimationEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitAnimationEvent where
  pFromJSVal :: JSVal -> WebKitAnimationEvent
pFromJSVal = JSVal -> WebKitAnimationEvent
WebKitAnimationEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitAnimationEvent where
  toJSVal :: WebKitAnimationEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitAnimationEvent -> JSVal)
-> WebKitAnimationEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitAnimationEvent -> JSVal
unWebKitAnimationEvent
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitAnimationEvent where
  fromJSVal :: JSVal -> JSM (Maybe WebKitAnimationEvent)
fromJSVal JSVal
v = (JSVal -> WebKitAnimationEvent)
-> Maybe JSVal -> Maybe WebKitAnimationEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitAnimationEvent
WebKitAnimationEvent (Maybe JSVal -> Maybe WebKitAnimationEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitAnimationEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitAnimationEvent
fromJSValUnchecked = WebKitAnimationEvent -> JSM WebKitAnimationEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitAnimationEvent -> JSM WebKitAnimationEvent)
-> (JSVal -> WebKitAnimationEvent)
-> JSVal
-> JSM WebKitAnimationEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitAnimationEvent
WebKitAnimationEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitAnimationEvent where
  makeObject :: WebKitAnimationEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitAnimationEvent -> JSVal)
-> WebKitAnimationEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitAnimationEvent -> JSVal
unWebKitAnimationEvent

instance IsEvent WebKitAnimationEvent
instance IsGObject WebKitAnimationEvent where
  typeGType :: WebKitAnimationEvent -> JSM GType
typeGType WebKitAnimationEvent
_ = JSM GType
gTypeWebKitAnimationEvent
  {-# INLINE typeGType #-}

noWebKitAnimationEvent :: Maybe WebKitAnimationEvent
noWebKitAnimationEvent :: Maybe WebKitAnimationEvent
noWebKitAnimationEvent = Maybe WebKitAnimationEvent
forall a. Maybe a
Nothing
{-# INLINE noWebKitAnimationEvent #-}

gTypeWebKitAnimationEvent :: JSM GType
gTypeWebKitAnimationEvent :: JSM GType
gTypeWebKitAnimationEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitAnimationEvent"

-- | Functions for this inteface are in "JSDOM.WebKitAnimationEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitAnimationEventInit Mozilla WebKitAnimationEventInit documentation>
newtype WebKitAnimationEventInit = WebKitAnimationEventInit { WebKitAnimationEventInit -> JSVal
unWebKitAnimationEventInit :: JSVal }

instance PToJSVal WebKitAnimationEventInit where
  pToJSVal :: WebKitAnimationEventInit -> JSVal
pToJSVal = WebKitAnimationEventInit -> JSVal
unWebKitAnimationEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitAnimationEventInit where
  pFromJSVal :: JSVal -> WebKitAnimationEventInit
pFromJSVal = JSVal -> WebKitAnimationEventInit
WebKitAnimationEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitAnimationEventInit where
  toJSVal :: WebKitAnimationEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitAnimationEventInit -> JSVal)
-> WebKitAnimationEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitAnimationEventInit -> JSVal
unWebKitAnimationEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitAnimationEventInit where
  fromJSVal :: JSVal -> JSM (Maybe WebKitAnimationEventInit)
fromJSVal JSVal
v = (JSVal -> WebKitAnimationEventInit)
-> Maybe JSVal -> Maybe WebKitAnimationEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitAnimationEventInit
WebKitAnimationEventInit (Maybe JSVal -> Maybe WebKitAnimationEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitAnimationEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitAnimationEventInit
fromJSValUnchecked = WebKitAnimationEventInit -> JSM WebKitAnimationEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitAnimationEventInit -> JSM WebKitAnimationEventInit)
-> (JSVal -> WebKitAnimationEventInit)
-> JSVal
-> JSM WebKitAnimationEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitAnimationEventInit
WebKitAnimationEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitAnimationEventInit where
  makeObject :: WebKitAnimationEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitAnimationEventInit -> JSVal)
-> WebKitAnimationEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitAnimationEventInit -> JSVal
unWebKitAnimationEventInit

instance IsEventInit WebKitAnimationEventInit
instance IsGObject WebKitAnimationEventInit where
  typeGType :: WebKitAnimationEventInit -> JSM GType
typeGType WebKitAnimationEventInit
_ = JSM GType
gTypeWebKitAnimationEventInit
  {-# INLINE typeGType #-}

noWebKitAnimationEventInit :: Maybe WebKitAnimationEventInit
noWebKitAnimationEventInit :: Maybe WebKitAnimationEventInit
noWebKitAnimationEventInit = Maybe WebKitAnimationEventInit
forall a. Maybe a
Nothing
{-# INLINE noWebKitAnimationEventInit #-}

gTypeWebKitAnimationEventInit :: JSM GType
gTypeWebKitAnimationEventInit :: JSM GType
gTypeWebKitAnimationEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitAnimationEventInit"

-- | Functions for this inteface are in "JSDOM.WebKitCSSMatrix".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitCSSMatrix Mozilla WebKitCSSMatrix documentation>
newtype WebKitCSSMatrix = WebKitCSSMatrix { WebKitCSSMatrix -> JSVal
unWebKitCSSMatrix :: JSVal }

instance PToJSVal WebKitCSSMatrix where
  pToJSVal :: WebKitCSSMatrix -> JSVal
pToJSVal = WebKitCSSMatrix -> JSVal
unWebKitCSSMatrix
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitCSSMatrix where
  pFromJSVal :: JSVal -> WebKitCSSMatrix
pFromJSVal = JSVal -> WebKitCSSMatrix
WebKitCSSMatrix
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitCSSMatrix where
  toJSVal :: WebKitCSSMatrix -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitCSSMatrix -> JSVal) -> WebKitCSSMatrix -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitCSSMatrix -> JSVal
unWebKitCSSMatrix
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitCSSMatrix where
  fromJSVal :: JSVal -> JSM (Maybe WebKitCSSMatrix)
fromJSVal JSVal
v = (JSVal -> WebKitCSSMatrix) -> Maybe JSVal -> Maybe WebKitCSSMatrix
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitCSSMatrix
WebKitCSSMatrix (Maybe JSVal -> Maybe WebKitCSSMatrix)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitCSSMatrix)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitCSSMatrix
fromJSValUnchecked = WebKitCSSMatrix -> JSM WebKitCSSMatrix
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitCSSMatrix -> JSM WebKitCSSMatrix)
-> (JSVal -> WebKitCSSMatrix) -> JSVal -> JSM WebKitCSSMatrix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitCSSMatrix
WebKitCSSMatrix
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitCSSMatrix where
  makeObject :: WebKitCSSMatrix -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitCSSMatrix -> JSVal) -> WebKitCSSMatrix -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitCSSMatrix -> JSVal
unWebKitCSSMatrix

instance IsGObject WebKitCSSMatrix where
  typeGType :: WebKitCSSMatrix -> JSM GType
typeGType WebKitCSSMatrix
_ = JSM GType
gTypeWebKitCSSMatrix
  {-# INLINE typeGType #-}

noWebKitCSSMatrix :: Maybe WebKitCSSMatrix
noWebKitCSSMatrix :: Maybe WebKitCSSMatrix
noWebKitCSSMatrix = Maybe WebKitCSSMatrix
forall a. Maybe a
Nothing
{-# INLINE noWebKitCSSMatrix #-}

gTypeWebKitCSSMatrix :: JSM GType
gTypeWebKitCSSMatrix :: JSM GType
gTypeWebKitCSSMatrix = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitCSSMatrix"

-- | Functions for this inteface are in "JSDOM.WebKitCSSRegionRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitCSSRegionRule Mozilla WebKitCSSRegionRule documentation>
newtype WebKitCSSRegionRule = WebKitCSSRegionRule { WebKitCSSRegionRule -> JSVal
unWebKitCSSRegionRule :: JSVal }

instance PToJSVal WebKitCSSRegionRule where
  pToJSVal :: WebKitCSSRegionRule -> JSVal
pToJSVal = WebKitCSSRegionRule -> JSVal
unWebKitCSSRegionRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitCSSRegionRule where
  pFromJSVal :: JSVal -> WebKitCSSRegionRule
pFromJSVal = JSVal -> WebKitCSSRegionRule
WebKitCSSRegionRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitCSSRegionRule where
  toJSVal :: WebKitCSSRegionRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitCSSRegionRule -> JSVal)
-> WebKitCSSRegionRule
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitCSSRegionRule -> JSVal
unWebKitCSSRegionRule
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitCSSRegionRule where
  fromJSVal :: JSVal -> JSM (Maybe WebKitCSSRegionRule)
fromJSVal JSVal
v = (JSVal -> WebKitCSSRegionRule)
-> Maybe JSVal -> Maybe WebKitCSSRegionRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitCSSRegionRule
WebKitCSSRegionRule (Maybe JSVal -> Maybe WebKitCSSRegionRule)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitCSSRegionRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitCSSRegionRule
fromJSValUnchecked = WebKitCSSRegionRule -> JSM WebKitCSSRegionRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitCSSRegionRule -> JSM WebKitCSSRegionRule)
-> (JSVal -> WebKitCSSRegionRule)
-> JSVal
-> JSM WebKitCSSRegionRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitCSSRegionRule
WebKitCSSRegionRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitCSSRegionRule where
  makeObject :: WebKitCSSRegionRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitCSSRegionRule -> JSVal)
-> WebKitCSSRegionRule
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitCSSRegionRule -> JSVal
unWebKitCSSRegionRule

instance IsCSSRule WebKitCSSRegionRule
instance IsGObject WebKitCSSRegionRule where
  typeGType :: WebKitCSSRegionRule -> JSM GType
typeGType WebKitCSSRegionRule
_ = JSM GType
gTypeWebKitCSSRegionRule
  {-# INLINE typeGType #-}

noWebKitCSSRegionRule :: Maybe WebKitCSSRegionRule
noWebKitCSSRegionRule :: Maybe WebKitCSSRegionRule
noWebKitCSSRegionRule = Maybe WebKitCSSRegionRule
forall a. Maybe a
Nothing
{-# INLINE noWebKitCSSRegionRule #-}

gTypeWebKitCSSRegionRule :: JSM GType
gTypeWebKitCSSRegionRule :: JSM GType
gTypeWebKitCSSRegionRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitCSSRegionRule"

-- | Functions for this inteface are in "JSDOM.WebKitCSSViewportRule".
-- Base interface functions are in:
--
--     * "JSDOM.CSSRule"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitCSSViewportRule Mozilla WebKitCSSViewportRule documentation>
newtype WebKitCSSViewportRule = WebKitCSSViewportRule { WebKitCSSViewportRule -> JSVal
unWebKitCSSViewportRule :: JSVal }

instance PToJSVal WebKitCSSViewportRule where
  pToJSVal :: WebKitCSSViewportRule -> JSVal
pToJSVal = WebKitCSSViewportRule -> JSVal
unWebKitCSSViewportRule
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitCSSViewportRule where
  pFromJSVal :: JSVal -> WebKitCSSViewportRule
pFromJSVal = JSVal -> WebKitCSSViewportRule
WebKitCSSViewportRule
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitCSSViewportRule where
  toJSVal :: WebKitCSSViewportRule -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitCSSViewportRule -> JSVal)
-> WebKitCSSViewportRule
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitCSSViewportRule -> JSVal
unWebKitCSSViewportRule
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitCSSViewportRule where
  fromJSVal :: JSVal -> JSM (Maybe WebKitCSSViewportRule)
fromJSVal JSVal
v = (JSVal -> WebKitCSSViewportRule)
-> Maybe JSVal -> Maybe WebKitCSSViewportRule
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitCSSViewportRule
WebKitCSSViewportRule (Maybe JSVal -> Maybe WebKitCSSViewportRule)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitCSSViewportRule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitCSSViewportRule
fromJSValUnchecked = WebKitCSSViewportRule -> JSM WebKitCSSViewportRule
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitCSSViewportRule -> JSM WebKitCSSViewportRule)
-> (JSVal -> WebKitCSSViewportRule)
-> JSVal
-> JSM WebKitCSSViewportRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitCSSViewportRule
WebKitCSSViewportRule
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitCSSViewportRule where
  makeObject :: WebKitCSSViewportRule -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitCSSViewportRule -> JSVal)
-> WebKitCSSViewportRule
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitCSSViewportRule -> JSVal
unWebKitCSSViewportRule

instance IsCSSRule WebKitCSSViewportRule
instance IsGObject WebKitCSSViewportRule where
  typeGType :: WebKitCSSViewportRule -> JSM GType
typeGType WebKitCSSViewportRule
_ = JSM GType
gTypeWebKitCSSViewportRule
  {-# INLINE typeGType #-}

noWebKitCSSViewportRule :: Maybe WebKitCSSViewportRule
noWebKitCSSViewportRule :: Maybe WebKitCSSViewportRule
noWebKitCSSViewportRule = Maybe WebKitCSSViewportRule
forall a. Maybe a
Nothing
{-# INLINE noWebKitCSSViewportRule #-}

gTypeWebKitCSSViewportRule :: JSM GType
gTypeWebKitCSSViewportRule :: JSM GType
gTypeWebKitCSSViewportRule = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitCSSViewportRule"

-- | Functions for this inteface are in "JSDOM.WebKitMediaKeyError".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitMediaKeyError Mozilla WebKitMediaKeyError documentation>
newtype WebKitMediaKeyError = WebKitMediaKeyError { WebKitMediaKeyError -> JSVal
unWebKitMediaKeyError :: JSVal }

instance PToJSVal WebKitMediaKeyError where
  pToJSVal :: WebKitMediaKeyError -> JSVal
pToJSVal = WebKitMediaKeyError -> JSVal
unWebKitMediaKeyError
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitMediaKeyError where
  pFromJSVal :: JSVal -> WebKitMediaKeyError
pFromJSVal = JSVal -> WebKitMediaKeyError
WebKitMediaKeyError
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitMediaKeyError where
  toJSVal :: WebKitMediaKeyError -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitMediaKeyError -> JSVal)
-> WebKitMediaKeyError
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeyError -> JSVal
unWebKitMediaKeyError
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitMediaKeyError where
  fromJSVal :: JSVal -> JSM (Maybe WebKitMediaKeyError)
fromJSVal JSVal
v = (JSVal -> WebKitMediaKeyError)
-> Maybe JSVal -> Maybe WebKitMediaKeyError
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitMediaKeyError
WebKitMediaKeyError (Maybe JSVal -> Maybe WebKitMediaKeyError)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitMediaKeyError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitMediaKeyError
fromJSValUnchecked = WebKitMediaKeyError -> JSM WebKitMediaKeyError
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitMediaKeyError -> JSM WebKitMediaKeyError)
-> (JSVal -> WebKitMediaKeyError)
-> JSVal
-> JSM WebKitMediaKeyError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitMediaKeyError
WebKitMediaKeyError
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitMediaKeyError where
  makeObject :: WebKitMediaKeyError -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitMediaKeyError -> JSVal)
-> WebKitMediaKeyError
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeyError -> JSVal
unWebKitMediaKeyError

instance IsGObject WebKitMediaKeyError where
  typeGType :: WebKitMediaKeyError -> JSM GType
typeGType WebKitMediaKeyError
_ = JSM GType
gTypeWebKitMediaKeyError
  {-# INLINE typeGType #-}

noWebKitMediaKeyError :: Maybe WebKitMediaKeyError
noWebKitMediaKeyError :: Maybe WebKitMediaKeyError
noWebKitMediaKeyError = Maybe WebKitMediaKeyError
forall a. Maybe a
Nothing
{-# INLINE noWebKitMediaKeyError #-}

gTypeWebKitMediaKeyError :: JSM GType
gTypeWebKitMediaKeyError :: JSM GType
gTypeWebKitMediaKeyError = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitMediaKeyError"

-- | Functions for this inteface are in "JSDOM.WebKitMediaKeyMessageEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitMediaKeyMessageEvent Mozilla WebKitMediaKeyMessageEvent documentation>
newtype WebKitMediaKeyMessageEvent = WebKitMediaKeyMessageEvent { WebKitMediaKeyMessageEvent -> JSVal
unWebKitMediaKeyMessageEvent :: JSVal }

instance PToJSVal WebKitMediaKeyMessageEvent where
  pToJSVal :: WebKitMediaKeyMessageEvent -> JSVal
pToJSVal = WebKitMediaKeyMessageEvent -> JSVal
unWebKitMediaKeyMessageEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitMediaKeyMessageEvent where
  pFromJSVal :: JSVal -> WebKitMediaKeyMessageEvent
pFromJSVal = JSVal -> WebKitMediaKeyMessageEvent
WebKitMediaKeyMessageEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitMediaKeyMessageEvent where
  toJSVal :: WebKitMediaKeyMessageEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitMediaKeyMessageEvent -> JSVal)
-> WebKitMediaKeyMessageEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeyMessageEvent -> JSVal
unWebKitMediaKeyMessageEvent
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitMediaKeyMessageEvent where
  fromJSVal :: JSVal -> JSM (Maybe WebKitMediaKeyMessageEvent)
fromJSVal JSVal
v = (JSVal -> WebKitMediaKeyMessageEvent)
-> Maybe JSVal -> Maybe WebKitMediaKeyMessageEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitMediaKeyMessageEvent
WebKitMediaKeyMessageEvent (Maybe JSVal -> Maybe WebKitMediaKeyMessageEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitMediaKeyMessageEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitMediaKeyMessageEvent
fromJSValUnchecked = WebKitMediaKeyMessageEvent -> JSM WebKitMediaKeyMessageEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitMediaKeyMessageEvent -> JSM WebKitMediaKeyMessageEvent)
-> (JSVal -> WebKitMediaKeyMessageEvent)
-> JSVal
-> JSM WebKitMediaKeyMessageEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitMediaKeyMessageEvent
WebKitMediaKeyMessageEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitMediaKeyMessageEvent where
  makeObject :: WebKitMediaKeyMessageEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitMediaKeyMessageEvent -> JSVal)
-> WebKitMediaKeyMessageEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeyMessageEvent -> JSVal
unWebKitMediaKeyMessageEvent

instance IsEvent WebKitMediaKeyMessageEvent
instance IsGObject WebKitMediaKeyMessageEvent where
  typeGType :: WebKitMediaKeyMessageEvent -> JSM GType
typeGType WebKitMediaKeyMessageEvent
_ = JSM GType
gTypeWebKitMediaKeyMessageEvent
  {-# INLINE typeGType #-}

noWebKitMediaKeyMessageEvent :: Maybe WebKitMediaKeyMessageEvent
noWebKitMediaKeyMessageEvent :: Maybe WebKitMediaKeyMessageEvent
noWebKitMediaKeyMessageEvent = Maybe WebKitMediaKeyMessageEvent
forall a. Maybe a
Nothing
{-# INLINE noWebKitMediaKeyMessageEvent #-}

gTypeWebKitMediaKeyMessageEvent :: JSM GType
gTypeWebKitMediaKeyMessageEvent :: JSM GType
gTypeWebKitMediaKeyMessageEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitMediaKeyMessageEvent"

-- | Functions for this inteface are in "JSDOM.WebKitMediaKeyMessageEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitMediaKeyMessageEventInit Mozilla WebKitMediaKeyMessageEventInit documentation>
newtype WebKitMediaKeyMessageEventInit = WebKitMediaKeyMessageEventInit { WebKitMediaKeyMessageEventInit -> JSVal
unWebKitMediaKeyMessageEventInit :: JSVal }

instance PToJSVal WebKitMediaKeyMessageEventInit where
  pToJSVal :: WebKitMediaKeyMessageEventInit -> JSVal
pToJSVal = WebKitMediaKeyMessageEventInit -> JSVal
unWebKitMediaKeyMessageEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitMediaKeyMessageEventInit where
  pFromJSVal :: JSVal -> WebKitMediaKeyMessageEventInit
pFromJSVal = JSVal -> WebKitMediaKeyMessageEventInit
WebKitMediaKeyMessageEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitMediaKeyMessageEventInit where
  toJSVal :: WebKitMediaKeyMessageEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitMediaKeyMessageEventInit -> JSVal)
-> WebKitMediaKeyMessageEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeyMessageEventInit -> JSVal
unWebKitMediaKeyMessageEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitMediaKeyMessageEventInit where
  fromJSVal :: JSVal -> JSM (Maybe WebKitMediaKeyMessageEventInit)
fromJSVal JSVal
v = (JSVal -> WebKitMediaKeyMessageEventInit)
-> Maybe JSVal -> Maybe WebKitMediaKeyMessageEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitMediaKeyMessageEventInit
WebKitMediaKeyMessageEventInit (Maybe JSVal -> Maybe WebKitMediaKeyMessageEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitMediaKeyMessageEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitMediaKeyMessageEventInit
fromJSValUnchecked = WebKitMediaKeyMessageEventInit
-> JSM WebKitMediaKeyMessageEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitMediaKeyMessageEventInit
 -> JSM WebKitMediaKeyMessageEventInit)
-> (JSVal -> WebKitMediaKeyMessageEventInit)
-> JSVal
-> JSM WebKitMediaKeyMessageEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitMediaKeyMessageEventInit
WebKitMediaKeyMessageEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitMediaKeyMessageEventInit where
  makeObject :: WebKitMediaKeyMessageEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitMediaKeyMessageEventInit -> JSVal)
-> WebKitMediaKeyMessageEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeyMessageEventInit -> JSVal
unWebKitMediaKeyMessageEventInit

instance IsEventInit WebKitMediaKeyMessageEventInit
instance IsGObject WebKitMediaKeyMessageEventInit where
  typeGType :: WebKitMediaKeyMessageEventInit -> JSM GType
typeGType WebKitMediaKeyMessageEventInit
_ = JSM GType
gTypeWebKitMediaKeyMessageEventInit
  {-# INLINE typeGType #-}

noWebKitMediaKeyMessageEventInit :: Maybe WebKitMediaKeyMessageEventInit
noWebKitMediaKeyMessageEventInit :: Maybe WebKitMediaKeyMessageEventInit
noWebKitMediaKeyMessageEventInit = Maybe WebKitMediaKeyMessageEventInit
forall a. Maybe a
Nothing
{-# INLINE noWebKitMediaKeyMessageEventInit #-}

gTypeWebKitMediaKeyMessageEventInit :: JSM GType
gTypeWebKitMediaKeyMessageEventInit :: JSM GType
gTypeWebKitMediaKeyMessageEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitMediaKeyMessageEventInit"

-- | Functions for this inteface are in "JSDOM.WebKitMediaKeyNeededEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitMediaKeyNeededEvent Mozilla WebKitMediaKeyNeededEvent documentation>
newtype WebKitMediaKeyNeededEvent = WebKitMediaKeyNeededEvent { WebKitMediaKeyNeededEvent -> JSVal
unWebKitMediaKeyNeededEvent :: JSVal }

instance PToJSVal WebKitMediaKeyNeededEvent where
  pToJSVal :: WebKitMediaKeyNeededEvent -> JSVal
pToJSVal = WebKitMediaKeyNeededEvent -> JSVal
unWebKitMediaKeyNeededEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitMediaKeyNeededEvent where
  pFromJSVal :: JSVal -> WebKitMediaKeyNeededEvent
pFromJSVal = JSVal -> WebKitMediaKeyNeededEvent
WebKitMediaKeyNeededEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitMediaKeyNeededEvent where
  toJSVal :: WebKitMediaKeyNeededEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitMediaKeyNeededEvent -> JSVal)
-> WebKitMediaKeyNeededEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeyNeededEvent -> JSVal
unWebKitMediaKeyNeededEvent
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitMediaKeyNeededEvent where
  fromJSVal :: JSVal -> JSM (Maybe WebKitMediaKeyNeededEvent)
fromJSVal JSVal
v = (JSVal -> WebKitMediaKeyNeededEvent)
-> Maybe JSVal -> Maybe WebKitMediaKeyNeededEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitMediaKeyNeededEvent
WebKitMediaKeyNeededEvent (Maybe JSVal -> Maybe WebKitMediaKeyNeededEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitMediaKeyNeededEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitMediaKeyNeededEvent
fromJSValUnchecked = WebKitMediaKeyNeededEvent -> JSM WebKitMediaKeyNeededEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitMediaKeyNeededEvent -> JSM WebKitMediaKeyNeededEvent)
-> (JSVal -> WebKitMediaKeyNeededEvent)
-> JSVal
-> JSM WebKitMediaKeyNeededEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitMediaKeyNeededEvent
WebKitMediaKeyNeededEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitMediaKeyNeededEvent where
  makeObject :: WebKitMediaKeyNeededEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitMediaKeyNeededEvent -> JSVal)
-> WebKitMediaKeyNeededEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeyNeededEvent -> JSVal
unWebKitMediaKeyNeededEvent

instance IsEvent WebKitMediaKeyNeededEvent
instance IsGObject WebKitMediaKeyNeededEvent where
  typeGType :: WebKitMediaKeyNeededEvent -> JSM GType
typeGType WebKitMediaKeyNeededEvent
_ = JSM GType
gTypeWebKitMediaKeyNeededEvent
  {-# INLINE typeGType #-}

noWebKitMediaKeyNeededEvent :: Maybe WebKitMediaKeyNeededEvent
noWebKitMediaKeyNeededEvent :: Maybe WebKitMediaKeyNeededEvent
noWebKitMediaKeyNeededEvent = Maybe WebKitMediaKeyNeededEvent
forall a. Maybe a
Nothing
{-# INLINE noWebKitMediaKeyNeededEvent #-}

gTypeWebKitMediaKeyNeededEvent :: JSM GType
gTypeWebKitMediaKeyNeededEvent :: JSM GType
gTypeWebKitMediaKeyNeededEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitMediaKeyNeededEvent"

-- | Functions for this inteface are in "JSDOM.WebKitMediaKeyNeededEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitMediaKeyNeededEventInit Mozilla WebKitMediaKeyNeededEventInit documentation>
newtype WebKitMediaKeyNeededEventInit = WebKitMediaKeyNeededEventInit { WebKitMediaKeyNeededEventInit -> JSVal
unWebKitMediaKeyNeededEventInit :: JSVal }

instance PToJSVal WebKitMediaKeyNeededEventInit where
  pToJSVal :: WebKitMediaKeyNeededEventInit -> JSVal
pToJSVal = WebKitMediaKeyNeededEventInit -> JSVal
unWebKitMediaKeyNeededEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitMediaKeyNeededEventInit where
  pFromJSVal :: JSVal -> WebKitMediaKeyNeededEventInit
pFromJSVal = JSVal -> WebKitMediaKeyNeededEventInit
WebKitMediaKeyNeededEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitMediaKeyNeededEventInit where
  toJSVal :: WebKitMediaKeyNeededEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitMediaKeyNeededEventInit -> JSVal)
-> WebKitMediaKeyNeededEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeyNeededEventInit -> JSVal
unWebKitMediaKeyNeededEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitMediaKeyNeededEventInit where
  fromJSVal :: JSVal -> JSM (Maybe WebKitMediaKeyNeededEventInit)
fromJSVal JSVal
v = (JSVal -> WebKitMediaKeyNeededEventInit)
-> Maybe JSVal -> Maybe WebKitMediaKeyNeededEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitMediaKeyNeededEventInit
WebKitMediaKeyNeededEventInit (Maybe JSVal -> Maybe WebKitMediaKeyNeededEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitMediaKeyNeededEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitMediaKeyNeededEventInit
fromJSValUnchecked = WebKitMediaKeyNeededEventInit -> JSM WebKitMediaKeyNeededEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitMediaKeyNeededEventInit
 -> JSM WebKitMediaKeyNeededEventInit)
-> (JSVal -> WebKitMediaKeyNeededEventInit)
-> JSVal
-> JSM WebKitMediaKeyNeededEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitMediaKeyNeededEventInit
WebKitMediaKeyNeededEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitMediaKeyNeededEventInit where
  makeObject :: WebKitMediaKeyNeededEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitMediaKeyNeededEventInit -> JSVal)
-> WebKitMediaKeyNeededEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeyNeededEventInit -> JSVal
unWebKitMediaKeyNeededEventInit

instance IsEventInit WebKitMediaKeyNeededEventInit
instance IsGObject WebKitMediaKeyNeededEventInit where
  typeGType :: WebKitMediaKeyNeededEventInit -> JSM GType
typeGType WebKitMediaKeyNeededEventInit
_ = JSM GType
gTypeWebKitMediaKeyNeededEventInit
  {-# INLINE typeGType #-}

noWebKitMediaKeyNeededEventInit :: Maybe WebKitMediaKeyNeededEventInit
noWebKitMediaKeyNeededEventInit :: Maybe WebKitMediaKeyNeededEventInit
noWebKitMediaKeyNeededEventInit = Maybe WebKitMediaKeyNeededEventInit
forall a. Maybe a
Nothing
{-# INLINE noWebKitMediaKeyNeededEventInit #-}

gTypeWebKitMediaKeyNeededEventInit :: JSM GType
gTypeWebKitMediaKeyNeededEventInit :: JSM GType
gTypeWebKitMediaKeyNeededEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitMediaKeyNeededEventInit"

-- | Functions for this inteface are in "JSDOM.WebKitMediaKeySession".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitMediaKeySession Mozilla WebKitMediaKeySession documentation>
newtype WebKitMediaKeySession = WebKitMediaKeySession { WebKitMediaKeySession -> JSVal
unWebKitMediaKeySession :: JSVal }

instance PToJSVal WebKitMediaKeySession where
  pToJSVal :: WebKitMediaKeySession -> JSVal
pToJSVal = WebKitMediaKeySession -> JSVal
unWebKitMediaKeySession
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitMediaKeySession where
  pFromJSVal :: JSVal -> WebKitMediaKeySession
pFromJSVal = JSVal -> WebKitMediaKeySession
WebKitMediaKeySession
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitMediaKeySession where
  toJSVal :: WebKitMediaKeySession -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitMediaKeySession -> JSVal)
-> WebKitMediaKeySession
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeySession -> JSVal
unWebKitMediaKeySession
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitMediaKeySession where
  fromJSVal :: JSVal -> JSM (Maybe WebKitMediaKeySession)
fromJSVal JSVal
v = (JSVal -> WebKitMediaKeySession)
-> Maybe JSVal -> Maybe WebKitMediaKeySession
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitMediaKeySession
WebKitMediaKeySession (Maybe JSVal -> Maybe WebKitMediaKeySession)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitMediaKeySession)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitMediaKeySession
fromJSValUnchecked = WebKitMediaKeySession -> JSM WebKitMediaKeySession
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitMediaKeySession -> JSM WebKitMediaKeySession)
-> (JSVal -> WebKitMediaKeySession)
-> JSVal
-> JSM WebKitMediaKeySession
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitMediaKeySession
WebKitMediaKeySession
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitMediaKeySession where
  makeObject :: WebKitMediaKeySession -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitMediaKeySession -> JSVal)
-> WebKitMediaKeySession
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeySession -> JSVal
unWebKitMediaKeySession

instance IsEventTarget WebKitMediaKeySession
instance IsGObject WebKitMediaKeySession where
  typeGType :: WebKitMediaKeySession -> JSM GType
typeGType WebKitMediaKeySession
_ = JSM GType
gTypeWebKitMediaKeySession
  {-# INLINE typeGType #-}

noWebKitMediaKeySession :: Maybe WebKitMediaKeySession
noWebKitMediaKeySession :: Maybe WebKitMediaKeySession
noWebKitMediaKeySession = Maybe WebKitMediaKeySession
forall a. Maybe a
Nothing
{-# INLINE noWebKitMediaKeySession #-}

gTypeWebKitMediaKeySession :: JSM GType
gTypeWebKitMediaKeySession :: JSM GType
gTypeWebKitMediaKeySession = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitMediaKeySession"

-- | Functions for this inteface are in "JSDOM.WebKitMediaKeys".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitMediaKeys Mozilla WebKitMediaKeys documentation>
newtype WebKitMediaKeys = WebKitMediaKeys { WebKitMediaKeys -> JSVal
unWebKitMediaKeys :: JSVal }

instance PToJSVal WebKitMediaKeys where
  pToJSVal :: WebKitMediaKeys -> JSVal
pToJSVal = WebKitMediaKeys -> JSVal
unWebKitMediaKeys
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitMediaKeys where
  pFromJSVal :: JSVal -> WebKitMediaKeys
pFromJSVal = JSVal -> WebKitMediaKeys
WebKitMediaKeys
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitMediaKeys where
  toJSVal :: WebKitMediaKeys -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitMediaKeys -> JSVal) -> WebKitMediaKeys -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeys -> JSVal
unWebKitMediaKeys
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitMediaKeys where
  fromJSVal :: JSVal -> JSM (Maybe WebKitMediaKeys)
fromJSVal JSVal
v = (JSVal -> WebKitMediaKeys) -> Maybe JSVal -> Maybe WebKitMediaKeys
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitMediaKeys
WebKitMediaKeys (Maybe JSVal -> Maybe WebKitMediaKeys)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitMediaKeys)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitMediaKeys
fromJSValUnchecked = WebKitMediaKeys -> JSM WebKitMediaKeys
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitMediaKeys -> JSM WebKitMediaKeys)
-> (JSVal -> WebKitMediaKeys) -> JSVal -> JSM WebKitMediaKeys
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitMediaKeys
WebKitMediaKeys
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitMediaKeys where
  makeObject :: WebKitMediaKeys -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitMediaKeys -> JSVal) -> WebKitMediaKeys -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitMediaKeys -> JSVal
unWebKitMediaKeys

instance IsGObject WebKitMediaKeys where
  typeGType :: WebKitMediaKeys -> JSM GType
typeGType WebKitMediaKeys
_ = JSM GType
gTypeWebKitMediaKeys
  {-# INLINE typeGType #-}

noWebKitMediaKeys :: Maybe WebKitMediaKeys
noWebKitMediaKeys :: Maybe WebKitMediaKeys
noWebKitMediaKeys = Maybe WebKitMediaKeys
forall a. Maybe a
Nothing
{-# INLINE noWebKitMediaKeys #-}

gTypeWebKitMediaKeys :: JSM GType
gTypeWebKitMediaKeys :: JSM GType
gTypeWebKitMediaKeys = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitMediaKeys"

-- | Functions for this inteface are in "JSDOM.WebKitNamedFlow".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitNamedFlow Mozilla WebKitNamedFlow documentation>
newtype WebKitNamedFlow = WebKitNamedFlow { WebKitNamedFlow -> JSVal
unWebKitNamedFlow :: JSVal }

instance PToJSVal WebKitNamedFlow where
  pToJSVal :: WebKitNamedFlow -> JSVal
pToJSVal = WebKitNamedFlow -> JSVal
unWebKitNamedFlow
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitNamedFlow where
  pFromJSVal :: JSVal -> WebKitNamedFlow
pFromJSVal = JSVal -> WebKitNamedFlow
WebKitNamedFlow
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitNamedFlow where
  toJSVal :: WebKitNamedFlow -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitNamedFlow -> JSVal) -> WebKitNamedFlow -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitNamedFlow -> JSVal
unWebKitNamedFlow
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitNamedFlow where
  fromJSVal :: JSVal -> JSM (Maybe WebKitNamedFlow)
fromJSVal JSVal
v = (JSVal -> WebKitNamedFlow) -> Maybe JSVal -> Maybe WebKitNamedFlow
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitNamedFlow
WebKitNamedFlow (Maybe JSVal -> Maybe WebKitNamedFlow)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitNamedFlow)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitNamedFlow
fromJSValUnchecked = WebKitNamedFlow -> JSM WebKitNamedFlow
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitNamedFlow -> JSM WebKitNamedFlow)
-> (JSVal -> WebKitNamedFlow) -> JSVal -> JSM WebKitNamedFlow
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitNamedFlow
WebKitNamedFlow
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitNamedFlow where
  makeObject :: WebKitNamedFlow -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitNamedFlow -> JSVal) -> WebKitNamedFlow -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitNamedFlow -> JSVal
unWebKitNamedFlow

instance IsEventTarget WebKitNamedFlow
instance IsGObject WebKitNamedFlow where
  typeGType :: WebKitNamedFlow -> JSM GType
typeGType WebKitNamedFlow
_ = JSM GType
gTypeWebKitNamedFlow
  {-# INLINE typeGType #-}

noWebKitNamedFlow :: Maybe WebKitNamedFlow
noWebKitNamedFlow :: Maybe WebKitNamedFlow
noWebKitNamedFlow = Maybe WebKitNamedFlow
forall a. Maybe a
Nothing
{-# INLINE noWebKitNamedFlow #-}

gTypeWebKitNamedFlow :: JSM GType
gTypeWebKitNamedFlow :: JSM GType
gTypeWebKitNamedFlow = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitNamedFlow"

-- | Functions for this inteface are in "JSDOM.WebKitNamespace".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitNamespace Mozilla WebKitNamespace documentation>
newtype WebKitNamespace = WebKitNamespace { WebKitNamespace -> JSVal
unWebKitNamespace :: JSVal }

instance PToJSVal WebKitNamespace where
  pToJSVal :: WebKitNamespace -> JSVal
pToJSVal = WebKitNamespace -> JSVal
unWebKitNamespace
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitNamespace where
  pFromJSVal :: JSVal -> WebKitNamespace
pFromJSVal = JSVal -> WebKitNamespace
WebKitNamespace
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitNamespace where
  toJSVal :: WebKitNamespace -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitNamespace -> JSVal) -> WebKitNamespace -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitNamespace -> JSVal
unWebKitNamespace
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitNamespace where
  fromJSVal :: JSVal -> JSM (Maybe WebKitNamespace)
fromJSVal JSVal
v = (JSVal -> WebKitNamespace) -> Maybe JSVal -> Maybe WebKitNamespace
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitNamespace
WebKitNamespace (Maybe JSVal -> Maybe WebKitNamespace)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitNamespace)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitNamespace
fromJSValUnchecked = WebKitNamespace -> JSM WebKitNamespace
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitNamespace -> JSM WebKitNamespace)
-> (JSVal -> WebKitNamespace) -> JSVal -> JSM WebKitNamespace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitNamespace
WebKitNamespace
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitNamespace where
  makeObject :: WebKitNamespace -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitNamespace -> JSVal) -> WebKitNamespace -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitNamespace -> JSVal
unWebKitNamespace

instance IsGObject WebKitNamespace where
  typeGType :: WebKitNamespace -> JSM GType
typeGType WebKitNamespace
_ = JSM GType
gTypeWebKitNamespace
  {-# INLINE typeGType #-}

noWebKitNamespace :: Maybe WebKitNamespace
noWebKitNamespace :: Maybe WebKitNamespace
noWebKitNamespace = Maybe WebKitNamespace
forall a. Maybe a
Nothing
{-# INLINE noWebKitNamespace #-}

gTypeWebKitNamespace :: JSM GType
gTypeWebKitNamespace :: JSM GType
gTypeWebKitNamespace = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitNamespace"

-- | Functions for this inteface are in "JSDOM.WebKitPlaybackTargetAvailabilityEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitPlaybackTargetAvailabilityEvent Mozilla WebKitPlaybackTargetAvailabilityEvent documentation>
newtype WebKitPlaybackTargetAvailabilityEvent = WebKitPlaybackTargetAvailabilityEvent { WebKitPlaybackTargetAvailabilityEvent -> JSVal
unWebKitPlaybackTargetAvailabilityEvent :: JSVal }

instance PToJSVal WebKitPlaybackTargetAvailabilityEvent where
  pToJSVal :: WebKitPlaybackTargetAvailabilityEvent -> JSVal
pToJSVal = WebKitPlaybackTargetAvailabilityEvent -> JSVal
unWebKitPlaybackTargetAvailabilityEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitPlaybackTargetAvailabilityEvent where
  pFromJSVal :: JSVal -> WebKitPlaybackTargetAvailabilityEvent
pFromJSVal = JSVal -> WebKitPlaybackTargetAvailabilityEvent
WebKitPlaybackTargetAvailabilityEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitPlaybackTargetAvailabilityEvent where
  toJSVal :: WebKitPlaybackTargetAvailabilityEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitPlaybackTargetAvailabilityEvent -> JSVal)
-> WebKitPlaybackTargetAvailabilityEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitPlaybackTargetAvailabilityEvent -> JSVal
unWebKitPlaybackTargetAvailabilityEvent
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitPlaybackTargetAvailabilityEvent where
  fromJSVal :: JSVal -> JSM (Maybe WebKitPlaybackTargetAvailabilityEvent)
fromJSVal JSVal
v = (JSVal -> WebKitPlaybackTargetAvailabilityEvent)
-> Maybe JSVal -> Maybe WebKitPlaybackTargetAvailabilityEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitPlaybackTargetAvailabilityEvent
WebKitPlaybackTargetAvailabilityEvent (Maybe JSVal -> Maybe WebKitPlaybackTargetAvailabilityEvent)
-> JSM (Maybe JSVal)
-> JSM (Maybe WebKitPlaybackTargetAvailabilityEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitPlaybackTargetAvailabilityEvent
fromJSValUnchecked = WebKitPlaybackTargetAvailabilityEvent
-> JSM WebKitPlaybackTargetAvailabilityEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitPlaybackTargetAvailabilityEvent
 -> JSM WebKitPlaybackTargetAvailabilityEvent)
-> (JSVal -> WebKitPlaybackTargetAvailabilityEvent)
-> JSVal
-> JSM WebKitPlaybackTargetAvailabilityEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitPlaybackTargetAvailabilityEvent
WebKitPlaybackTargetAvailabilityEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitPlaybackTargetAvailabilityEvent where
  makeObject :: WebKitPlaybackTargetAvailabilityEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitPlaybackTargetAvailabilityEvent -> JSVal)
-> WebKitPlaybackTargetAvailabilityEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitPlaybackTargetAvailabilityEvent -> JSVal
unWebKitPlaybackTargetAvailabilityEvent

instance IsEvent WebKitPlaybackTargetAvailabilityEvent
instance IsGObject WebKitPlaybackTargetAvailabilityEvent where
  typeGType :: WebKitPlaybackTargetAvailabilityEvent -> JSM GType
typeGType WebKitPlaybackTargetAvailabilityEvent
_ = JSM GType
gTypeWebKitPlaybackTargetAvailabilityEvent
  {-# INLINE typeGType #-}

noWebKitPlaybackTargetAvailabilityEvent :: Maybe WebKitPlaybackTargetAvailabilityEvent
noWebKitPlaybackTargetAvailabilityEvent :: Maybe WebKitPlaybackTargetAvailabilityEvent
noWebKitPlaybackTargetAvailabilityEvent = Maybe WebKitPlaybackTargetAvailabilityEvent
forall a. Maybe a
Nothing
{-# INLINE noWebKitPlaybackTargetAvailabilityEvent #-}

gTypeWebKitPlaybackTargetAvailabilityEvent :: JSM GType
gTypeWebKitPlaybackTargetAvailabilityEvent :: JSM GType
gTypeWebKitPlaybackTargetAvailabilityEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitPlaybackTargetAvailabilityEvent"

-- | Functions for this inteface are in "JSDOM.WebKitPlaybackTargetAvailabilityEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitPlaybackTargetAvailabilityEventInit Mozilla WebKitPlaybackTargetAvailabilityEventInit documentation>
newtype WebKitPlaybackTargetAvailabilityEventInit = WebKitPlaybackTargetAvailabilityEventInit { WebKitPlaybackTargetAvailabilityEventInit -> JSVal
unWebKitPlaybackTargetAvailabilityEventInit :: JSVal }

instance PToJSVal WebKitPlaybackTargetAvailabilityEventInit where
  pToJSVal :: WebKitPlaybackTargetAvailabilityEventInit -> JSVal
pToJSVal = WebKitPlaybackTargetAvailabilityEventInit -> JSVal
unWebKitPlaybackTargetAvailabilityEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitPlaybackTargetAvailabilityEventInit where
  pFromJSVal :: JSVal -> WebKitPlaybackTargetAvailabilityEventInit
pFromJSVal = JSVal -> WebKitPlaybackTargetAvailabilityEventInit
WebKitPlaybackTargetAvailabilityEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitPlaybackTargetAvailabilityEventInit where
  toJSVal :: WebKitPlaybackTargetAvailabilityEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitPlaybackTargetAvailabilityEventInit -> JSVal)
-> WebKitPlaybackTargetAvailabilityEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitPlaybackTargetAvailabilityEventInit -> JSVal
unWebKitPlaybackTargetAvailabilityEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitPlaybackTargetAvailabilityEventInit where
  fromJSVal :: JSVal -> JSM (Maybe WebKitPlaybackTargetAvailabilityEventInit)
fromJSVal JSVal
v = (JSVal -> WebKitPlaybackTargetAvailabilityEventInit)
-> Maybe JSVal -> Maybe WebKitPlaybackTargetAvailabilityEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitPlaybackTargetAvailabilityEventInit
WebKitPlaybackTargetAvailabilityEventInit (Maybe JSVal -> Maybe WebKitPlaybackTargetAvailabilityEventInit)
-> JSM (Maybe JSVal)
-> JSM (Maybe WebKitPlaybackTargetAvailabilityEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitPlaybackTargetAvailabilityEventInit
fromJSValUnchecked = WebKitPlaybackTargetAvailabilityEventInit
-> JSM WebKitPlaybackTargetAvailabilityEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitPlaybackTargetAvailabilityEventInit
 -> JSM WebKitPlaybackTargetAvailabilityEventInit)
-> (JSVal -> WebKitPlaybackTargetAvailabilityEventInit)
-> JSVal
-> JSM WebKitPlaybackTargetAvailabilityEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitPlaybackTargetAvailabilityEventInit
WebKitPlaybackTargetAvailabilityEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitPlaybackTargetAvailabilityEventInit where
  makeObject :: WebKitPlaybackTargetAvailabilityEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitPlaybackTargetAvailabilityEventInit -> JSVal)
-> WebKitPlaybackTargetAvailabilityEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitPlaybackTargetAvailabilityEventInit -> JSVal
unWebKitPlaybackTargetAvailabilityEventInit

instance IsEventInit WebKitPlaybackTargetAvailabilityEventInit
instance IsGObject WebKitPlaybackTargetAvailabilityEventInit where
  typeGType :: WebKitPlaybackTargetAvailabilityEventInit -> JSM GType
typeGType WebKitPlaybackTargetAvailabilityEventInit
_ = JSM GType
gTypeWebKitPlaybackTargetAvailabilityEventInit
  {-# INLINE typeGType #-}

noWebKitPlaybackTargetAvailabilityEventInit :: Maybe WebKitPlaybackTargetAvailabilityEventInit
noWebKitPlaybackTargetAvailabilityEventInit :: Maybe WebKitPlaybackTargetAvailabilityEventInit
noWebKitPlaybackTargetAvailabilityEventInit = Maybe WebKitPlaybackTargetAvailabilityEventInit
forall a. Maybe a
Nothing
{-# INLINE noWebKitPlaybackTargetAvailabilityEventInit #-}

gTypeWebKitPlaybackTargetAvailabilityEventInit :: JSM GType
gTypeWebKitPlaybackTargetAvailabilityEventInit :: JSM GType
gTypeWebKitPlaybackTargetAvailabilityEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitPlaybackTargetAvailabilityEventInit"

-- | Functions for this inteface are in "JSDOM.WebKitPoint".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitPoint Mozilla WebKitPoint documentation>
newtype WebKitPoint = WebKitPoint { WebKitPoint -> JSVal
unWebKitPoint :: JSVal }

instance PToJSVal WebKitPoint where
  pToJSVal :: WebKitPoint -> JSVal
pToJSVal = WebKitPoint -> JSVal
unWebKitPoint
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitPoint where
  pFromJSVal :: JSVal -> WebKitPoint
pFromJSVal = JSVal -> WebKitPoint
WebKitPoint
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitPoint where
  toJSVal :: WebKitPoint -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitPoint -> JSVal) -> WebKitPoint -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitPoint -> JSVal
unWebKitPoint
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitPoint where
  fromJSVal :: JSVal -> JSM (Maybe WebKitPoint)
fromJSVal JSVal
v = (JSVal -> WebKitPoint) -> Maybe JSVal -> Maybe WebKitPoint
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitPoint
WebKitPoint (Maybe JSVal -> Maybe WebKitPoint)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitPoint)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitPoint
fromJSValUnchecked = WebKitPoint -> JSM WebKitPoint
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitPoint -> JSM WebKitPoint)
-> (JSVal -> WebKitPoint) -> JSVal -> JSM WebKitPoint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitPoint
WebKitPoint
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitPoint where
  makeObject :: WebKitPoint -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitPoint -> JSVal) -> WebKitPoint -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitPoint -> JSVal
unWebKitPoint

instance IsGObject WebKitPoint where
  typeGType :: WebKitPoint -> JSM GType
typeGType WebKitPoint
_ = JSM GType
gTypeWebKitPoint
  {-# INLINE typeGType #-}

noWebKitPoint :: Maybe WebKitPoint
noWebKitPoint :: Maybe WebKitPoint
noWebKitPoint = Maybe WebKitPoint
forall a. Maybe a
Nothing
{-# INLINE noWebKitPoint #-}

gTypeWebKitPoint :: JSM GType
gTypeWebKitPoint :: JSM GType
gTypeWebKitPoint = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitPoint"

-- | Functions for this inteface are in "JSDOM.WebKitSubtleCrypto".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitSubtleCrypto Mozilla WebKitSubtleCrypto documentation>
newtype WebKitSubtleCrypto = WebKitSubtleCrypto { WebKitSubtleCrypto -> JSVal
unWebKitSubtleCrypto :: JSVal }

instance PToJSVal WebKitSubtleCrypto where
  pToJSVal :: WebKitSubtleCrypto -> JSVal
pToJSVal = WebKitSubtleCrypto -> JSVal
unWebKitSubtleCrypto
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitSubtleCrypto where
  pFromJSVal :: JSVal -> WebKitSubtleCrypto
pFromJSVal = JSVal -> WebKitSubtleCrypto
WebKitSubtleCrypto
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitSubtleCrypto where
  toJSVal :: WebKitSubtleCrypto -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitSubtleCrypto -> JSVal) -> WebKitSubtleCrypto -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitSubtleCrypto -> JSVal
unWebKitSubtleCrypto
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitSubtleCrypto where
  fromJSVal :: JSVal -> JSM (Maybe WebKitSubtleCrypto)
fromJSVal JSVal
v = (JSVal -> WebKitSubtleCrypto)
-> Maybe JSVal -> Maybe WebKitSubtleCrypto
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitSubtleCrypto
WebKitSubtleCrypto (Maybe JSVal -> Maybe WebKitSubtleCrypto)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitSubtleCrypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitSubtleCrypto
fromJSValUnchecked = WebKitSubtleCrypto -> JSM WebKitSubtleCrypto
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitSubtleCrypto -> JSM WebKitSubtleCrypto)
-> (JSVal -> WebKitSubtleCrypto) -> JSVal -> JSM WebKitSubtleCrypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitSubtleCrypto
WebKitSubtleCrypto
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitSubtleCrypto where
  makeObject :: WebKitSubtleCrypto -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitSubtleCrypto -> JSVal)
-> WebKitSubtleCrypto
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitSubtleCrypto -> JSVal
unWebKitSubtleCrypto

instance IsGObject WebKitSubtleCrypto where
  typeGType :: WebKitSubtleCrypto -> JSM GType
typeGType WebKitSubtleCrypto
_ = JSM GType
gTypeWebKitSubtleCrypto
  {-# INLINE typeGType #-}

noWebKitSubtleCrypto :: Maybe WebKitSubtleCrypto
noWebKitSubtleCrypto :: Maybe WebKitSubtleCrypto
noWebKitSubtleCrypto = Maybe WebKitSubtleCrypto
forall a. Maybe a
Nothing
{-# INLINE noWebKitSubtleCrypto #-}

gTypeWebKitSubtleCrypto :: JSM GType
gTypeWebKitSubtleCrypto :: JSM GType
gTypeWebKitSubtleCrypto = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitSubtleCrypto"

-- | Functions for this inteface are in "JSDOM.WebKitTransitionEvent".
-- Base interface functions are in:
--
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitTransitionEvent Mozilla WebKitTransitionEvent documentation>
newtype WebKitTransitionEvent = WebKitTransitionEvent { WebKitTransitionEvent -> JSVal
unWebKitTransitionEvent :: JSVal }

instance PToJSVal WebKitTransitionEvent where
  pToJSVal :: WebKitTransitionEvent -> JSVal
pToJSVal = WebKitTransitionEvent -> JSVal
unWebKitTransitionEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitTransitionEvent where
  pFromJSVal :: JSVal -> WebKitTransitionEvent
pFromJSVal = JSVal -> WebKitTransitionEvent
WebKitTransitionEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitTransitionEvent where
  toJSVal :: WebKitTransitionEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitTransitionEvent -> JSVal)
-> WebKitTransitionEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitTransitionEvent -> JSVal
unWebKitTransitionEvent
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitTransitionEvent where
  fromJSVal :: JSVal -> JSM (Maybe WebKitTransitionEvent)
fromJSVal JSVal
v = (JSVal -> WebKitTransitionEvent)
-> Maybe JSVal -> Maybe WebKitTransitionEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitTransitionEvent
WebKitTransitionEvent (Maybe JSVal -> Maybe WebKitTransitionEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitTransitionEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitTransitionEvent
fromJSValUnchecked = WebKitTransitionEvent -> JSM WebKitTransitionEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitTransitionEvent -> JSM WebKitTransitionEvent)
-> (JSVal -> WebKitTransitionEvent)
-> JSVal
-> JSM WebKitTransitionEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitTransitionEvent
WebKitTransitionEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitTransitionEvent where
  makeObject :: WebKitTransitionEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitTransitionEvent -> JSVal)
-> WebKitTransitionEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitTransitionEvent -> JSVal
unWebKitTransitionEvent

instance IsEvent WebKitTransitionEvent
instance IsGObject WebKitTransitionEvent where
  typeGType :: WebKitTransitionEvent -> JSM GType
typeGType WebKitTransitionEvent
_ = JSM GType
gTypeWebKitTransitionEvent
  {-# INLINE typeGType #-}

noWebKitTransitionEvent :: Maybe WebKitTransitionEvent
noWebKitTransitionEvent :: Maybe WebKitTransitionEvent
noWebKitTransitionEvent = Maybe WebKitTransitionEvent
forall a. Maybe a
Nothing
{-# INLINE noWebKitTransitionEvent #-}

gTypeWebKitTransitionEvent :: JSM GType
gTypeWebKitTransitionEvent :: JSM GType
gTypeWebKitTransitionEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitTransitionEvent"

-- | Functions for this inteface are in "JSDOM.WebKitTransitionEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebKitTransitionEventInit Mozilla WebKitTransitionEventInit documentation>
newtype WebKitTransitionEventInit = WebKitTransitionEventInit { WebKitTransitionEventInit -> JSVal
unWebKitTransitionEventInit :: JSVal }

instance PToJSVal WebKitTransitionEventInit where
  pToJSVal :: WebKitTransitionEventInit -> JSVal
pToJSVal = WebKitTransitionEventInit -> JSVal
unWebKitTransitionEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebKitTransitionEventInit where
  pFromJSVal :: JSVal -> WebKitTransitionEventInit
pFromJSVal = JSVal -> WebKitTransitionEventInit
WebKitTransitionEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebKitTransitionEventInit where
  toJSVal :: WebKitTransitionEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebKitTransitionEventInit -> JSVal)
-> WebKitTransitionEventInit
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitTransitionEventInit -> JSVal
unWebKitTransitionEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal WebKitTransitionEventInit where
  fromJSVal :: JSVal -> JSM (Maybe WebKitTransitionEventInit)
fromJSVal JSVal
v = (JSVal -> WebKitTransitionEventInit)
-> Maybe JSVal -> Maybe WebKitTransitionEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebKitTransitionEventInit
WebKitTransitionEventInit (Maybe JSVal -> Maybe WebKitTransitionEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe WebKitTransitionEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebKitTransitionEventInit
fromJSValUnchecked = WebKitTransitionEventInit -> JSM WebKitTransitionEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebKitTransitionEventInit -> JSM WebKitTransitionEventInit)
-> (JSVal -> WebKitTransitionEventInit)
-> JSVal
-> JSM WebKitTransitionEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebKitTransitionEventInit
WebKitTransitionEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebKitTransitionEventInit where
  makeObject :: WebKitTransitionEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebKitTransitionEventInit -> JSVal)
-> WebKitTransitionEventInit
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebKitTransitionEventInit -> JSVal
unWebKitTransitionEventInit

instance IsEventInit WebKitTransitionEventInit
instance IsGObject WebKitTransitionEventInit where
  typeGType :: WebKitTransitionEventInit -> JSM GType
typeGType WebKitTransitionEventInit
_ = JSM GType
gTypeWebKitTransitionEventInit
  {-# INLINE typeGType #-}

noWebKitTransitionEventInit :: Maybe WebKitTransitionEventInit
noWebKitTransitionEventInit :: Maybe WebKitTransitionEventInit
noWebKitTransitionEventInit = Maybe WebKitTransitionEventInit
forall a. Maybe a
Nothing
{-# INLINE noWebKitTransitionEventInit #-}

gTypeWebKitTransitionEventInit :: JSM GType
gTypeWebKitTransitionEventInit :: JSM GType
gTypeWebKitTransitionEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebKitTransitionEventInit"

-- | Functions for this inteface are in "JSDOM.WebSocket".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WebSocket Mozilla WebSocket documentation>
newtype WebSocket = WebSocket { WebSocket -> JSVal
unWebSocket :: JSVal }

instance PToJSVal WebSocket where
  pToJSVal :: WebSocket -> JSVal
pToJSVal = WebSocket -> JSVal
unWebSocket
  {-# INLINE pToJSVal #-}

instance PFromJSVal WebSocket where
  pFromJSVal :: JSVal -> WebSocket
pFromJSVal = JSVal -> WebSocket
WebSocket
  {-# INLINE pFromJSVal #-}

instance ToJSVal WebSocket where
  toJSVal :: WebSocket -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WebSocket -> JSVal) -> WebSocket -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebSocket -> JSVal
unWebSocket
  {-# INLINE toJSVal #-}

instance FromJSVal WebSocket where
  fromJSVal :: JSVal -> JSM (Maybe WebSocket)
fromJSVal JSVal
v = (JSVal -> WebSocket) -> Maybe JSVal -> Maybe WebSocket
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WebSocket
WebSocket (Maybe JSVal -> Maybe WebSocket)
-> JSM (Maybe JSVal) -> JSM (Maybe WebSocket)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WebSocket
fromJSValUnchecked = WebSocket -> JSM WebSocket
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WebSocket -> JSM WebSocket)
-> (JSVal -> WebSocket) -> JSVal -> JSM WebSocket
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WebSocket
WebSocket
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WebSocket where
  makeObject :: WebSocket -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WebSocket -> JSVal) -> WebSocket -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebSocket -> JSVal
unWebSocket

instance IsEventTarget WebSocket
instance IsGObject WebSocket where
  typeGType :: WebSocket -> JSM GType
typeGType WebSocket
_ = JSM GType
gTypeWebSocket
  {-# INLINE typeGType #-}

noWebSocket :: Maybe WebSocket
noWebSocket :: Maybe WebSocket
noWebSocket = Maybe WebSocket
forall a. Maybe a
Nothing
{-# INLINE noWebSocket #-}

gTypeWebSocket :: JSM GType
gTypeWebSocket :: JSM GType
gTypeWebSocket = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WebSocket"

-- | Functions for this inteface are in "JSDOM.WheelEvent".
-- Base interface functions are in:
--
--     * "JSDOM.MouseEvent"
--     * "JSDOM.UIEvent"
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WheelEvent Mozilla WheelEvent documentation>
newtype WheelEvent = WheelEvent { WheelEvent -> JSVal
unWheelEvent :: JSVal }

instance PToJSVal WheelEvent where
  pToJSVal :: WheelEvent -> JSVal
pToJSVal = WheelEvent -> JSVal
unWheelEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal WheelEvent where
  pFromJSVal :: JSVal -> WheelEvent
pFromJSVal = JSVal -> WheelEvent
WheelEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal WheelEvent where
  toJSVal :: WheelEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WheelEvent -> JSVal) -> WheelEvent -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WheelEvent -> JSVal
unWheelEvent
  {-# INLINE toJSVal #-}

instance FromJSVal WheelEvent where
  fromJSVal :: JSVal -> JSM (Maybe WheelEvent)
fromJSVal JSVal
v = (JSVal -> WheelEvent) -> Maybe JSVal -> Maybe WheelEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WheelEvent
WheelEvent (Maybe JSVal -> Maybe WheelEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe WheelEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WheelEvent
fromJSValUnchecked = WheelEvent -> JSM WheelEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WheelEvent -> JSM WheelEvent)
-> (JSVal -> WheelEvent) -> JSVal -> JSM WheelEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WheelEvent
WheelEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WheelEvent where
  makeObject :: WheelEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WheelEvent -> JSVal) -> WheelEvent -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WheelEvent -> JSVal
unWheelEvent

instance IsMouseEvent WheelEvent
instance IsUIEvent WheelEvent
instance IsEvent WheelEvent
instance IsGObject WheelEvent where
  typeGType :: WheelEvent -> JSM GType
typeGType WheelEvent
_ = JSM GType
gTypeWheelEvent
  {-# INLINE typeGType #-}

noWheelEvent :: Maybe WheelEvent
noWheelEvent :: Maybe WheelEvent
noWheelEvent = Maybe WheelEvent
forall a. Maybe a
Nothing
{-# INLINE noWheelEvent #-}

gTypeWheelEvent :: JSM GType
gTypeWheelEvent :: JSM GType
gTypeWheelEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WheelEvent"

-- | Functions for this inteface are in "JSDOM.WheelEventInit".
-- Base interface functions are in:
--
--     * "JSDOM.MouseEventInit"
--     * "JSDOM.EventModifierInit"
--     * "JSDOM.UIEventInit"
--     * "JSDOM.EventInit"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WheelEventInit Mozilla WheelEventInit documentation>
newtype WheelEventInit = WheelEventInit { WheelEventInit -> JSVal
unWheelEventInit :: JSVal }

instance PToJSVal WheelEventInit where
  pToJSVal :: WheelEventInit -> JSVal
pToJSVal = WheelEventInit -> JSVal
unWheelEventInit
  {-# INLINE pToJSVal #-}

instance PFromJSVal WheelEventInit where
  pFromJSVal :: JSVal -> WheelEventInit
pFromJSVal = JSVal -> WheelEventInit
WheelEventInit
  {-# INLINE pFromJSVal #-}

instance ToJSVal WheelEventInit where
  toJSVal :: WheelEventInit -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WheelEventInit -> JSVal) -> WheelEventInit -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WheelEventInit -> JSVal
unWheelEventInit
  {-# INLINE toJSVal #-}

instance FromJSVal WheelEventInit where
  fromJSVal :: JSVal -> JSM (Maybe WheelEventInit)
fromJSVal JSVal
v = (JSVal -> WheelEventInit) -> Maybe JSVal -> Maybe WheelEventInit
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WheelEventInit
WheelEventInit (Maybe JSVal -> Maybe WheelEventInit)
-> JSM (Maybe JSVal) -> JSM (Maybe WheelEventInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WheelEventInit
fromJSValUnchecked = WheelEventInit -> JSM WheelEventInit
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WheelEventInit -> JSM WheelEventInit)
-> (JSVal -> WheelEventInit) -> JSVal -> JSM WheelEventInit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WheelEventInit
WheelEventInit
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WheelEventInit where
  makeObject :: WheelEventInit -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WheelEventInit -> JSVal) -> WheelEventInit -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WheelEventInit -> JSVal
unWheelEventInit

instance IsMouseEventInit WheelEventInit
instance IsEventModifierInit WheelEventInit
instance IsUIEventInit WheelEventInit
instance IsEventInit WheelEventInit
instance IsGObject WheelEventInit where
  typeGType :: WheelEventInit -> JSM GType
typeGType WheelEventInit
_ = JSM GType
gTypeWheelEventInit
  {-# INLINE typeGType #-}

noWheelEventInit :: Maybe WheelEventInit
noWheelEventInit :: Maybe WheelEventInit
noWheelEventInit = Maybe WheelEventInit
forall a. Maybe a
Nothing
{-# INLINE noWheelEventInit #-}

gTypeWheelEventInit :: JSM GType
gTypeWheelEventInit :: JSM GType
gTypeWheelEventInit = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WheelEventInit"

-- | Functions for this inteface are in "JSDOM.Window".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--     * "JSDOM.WindowOrWorkerGlobalScope"
--     * "JSDOM.WindowEventHandlers"
--     * "JSDOM.GlobalPerformance"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.GlobalCrypto"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Window Mozilla Window documentation>
newtype Window = Window { Window -> JSVal
unWindow :: JSVal }

instance PToJSVal Window where
  pToJSVal :: Window -> JSVal
pToJSVal = Window -> JSVal
unWindow
  {-# INLINE pToJSVal #-}

instance PFromJSVal Window where
  pFromJSVal :: JSVal -> Window
pFromJSVal = JSVal -> Window
Window
  {-# INLINE pFromJSVal #-}

instance ToJSVal Window where
  toJSVal :: Window -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Window -> JSVal) -> Window -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> JSVal
unWindow
  {-# INLINE toJSVal #-}

instance FromJSVal Window where
  fromJSVal :: JSVal -> JSM (Maybe Window)
fromJSVal JSVal
v = (JSVal -> Window) -> Maybe JSVal -> Maybe Window
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Window
Window (Maybe JSVal -> Maybe Window)
-> JSM (Maybe JSVal) -> JSM (Maybe Window)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Window
fromJSValUnchecked = Window -> JSM Window
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Window -> JSM Window) -> (JSVal -> Window) -> JSVal -> JSM Window
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Window
Window
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Window where
  makeObject :: Window -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Window -> JSVal) -> Window -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> JSVal
unWindow

instance IsEventTarget Window
instance IsWindowOrWorkerGlobalScope Window
instance IsWindowEventHandlers Window
instance IsGlobalPerformance Window
instance IsGlobalEventHandlers Window
instance IsGlobalCrypto Window
instance IsGObject Window where
  typeGType :: Window -> JSM GType
typeGType Window
_ = JSM GType
gTypeWindow
  {-# INLINE typeGType #-}

noWindow :: Maybe Window
noWindow :: Maybe Window
noWindow = Maybe Window
forall a. Maybe a
Nothing
{-# INLINE noWindow #-}

gTypeWindow :: JSM GType
gTypeWindow :: JSM GType
gTypeWindow = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Window"

-- | Functions for this inteface are in "JSDOM.WindowEventHandlers".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WindowEventHandlers Mozilla WindowEventHandlers documentation>
newtype WindowEventHandlers = WindowEventHandlers { WindowEventHandlers -> JSVal
unWindowEventHandlers :: JSVal }

instance PToJSVal WindowEventHandlers where
  pToJSVal :: WindowEventHandlers -> JSVal
pToJSVal = WindowEventHandlers -> JSVal
unWindowEventHandlers
  {-# INLINE pToJSVal #-}

instance PFromJSVal WindowEventHandlers where
  pFromJSVal :: JSVal -> WindowEventHandlers
pFromJSVal = JSVal -> WindowEventHandlers
WindowEventHandlers
  {-# INLINE pFromJSVal #-}

instance ToJSVal WindowEventHandlers where
  toJSVal :: WindowEventHandlers -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WindowEventHandlers -> JSVal)
-> WindowEventHandlers
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowEventHandlers -> JSVal
unWindowEventHandlers
  {-# INLINE toJSVal #-}

instance FromJSVal WindowEventHandlers where
  fromJSVal :: JSVal -> JSM (Maybe WindowEventHandlers)
fromJSVal JSVal
v = (JSVal -> WindowEventHandlers)
-> Maybe JSVal -> Maybe WindowEventHandlers
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WindowEventHandlers
WindowEventHandlers (Maybe JSVal -> Maybe WindowEventHandlers)
-> JSM (Maybe JSVal) -> JSM (Maybe WindowEventHandlers)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WindowEventHandlers
fromJSValUnchecked = WindowEventHandlers -> JSM WindowEventHandlers
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WindowEventHandlers -> JSM WindowEventHandlers)
-> (JSVal -> WindowEventHandlers)
-> JSVal
-> JSM WindowEventHandlers
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WindowEventHandlers
WindowEventHandlers
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WindowEventHandlers where
  makeObject :: WindowEventHandlers -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WindowEventHandlers -> JSVal)
-> WindowEventHandlers
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowEventHandlers -> JSVal
unWindowEventHandlers

class (IsGObject o) => IsWindowEventHandlers o
toWindowEventHandlers :: IsWindowEventHandlers o => o -> WindowEventHandlers
toWindowEventHandlers :: forall o. IsWindowEventHandlers o => o -> WindowEventHandlers
toWindowEventHandlers = JSVal -> WindowEventHandlers
WindowEventHandlers (JSVal -> WindowEventHandlers)
-> (o -> JSVal) -> o -> WindowEventHandlers
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsWindowEventHandlers WindowEventHandlers
instance IsGObject WindowEventHandlers where
  typeGType :: WindowEventHandlers -> JSM GType
typeGType WindowEventHandlers
_ = JSM GType
gTypeWindowEventHandlers
  {-# INLINE typeGType #-}

noWindowEventHandlers :: Maybe WindowEventHandlers
noWindowEventHandlers :: Maybe WindowEventHandlers
noWindowEventHandlers = Maybe WindowEventHandlers
forall a. Maybe a
Nothing
{-# INLINE noWindowEventHandlers #-}

gTypeWindowEventHandlers :: JSM GType
gTypeWindowEventHandlers :: JSM GType
gTypeWindowEventHandlers = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WindowEventHandlers"

-- | Functions for this inteface are in "JSDOM.WindowOrWorkerGlobalScope".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WindowOrWorkerGlobalScope Mozilla WindowOrWorkerGlobalScope documentation>
newtype WindowOrWorkerGlobalScope = WindowOrWorkerGlobalScope { WindowOrWorkerGlobalScope -> JSVal
unWindowOrWorkerGlobalScope :: JSVal }

instance PToJSVal WindowOrWorkerGlobalScope where
  pToJSVal :: WindowOrWorkerGlobalScope -> JSVal
pToJSVal = WindowOrWorkerGlobalScope -> JSVal
unWindowOrWorkerGlobalScope
  {-# INLINE pToJSVal #-}

instance PFromJSVal WindowOrWorkerGlobalScope where
  pFromJSVal :: JSVal -> WindowOrWorkerGlobalScope
pFromJSVal = JSVal -> WindowOrWorkerGlobalScope
WindowOrWorkerGlobalScope
  {-# INLINE pFromJSVal #-}

instance ToJSVal WindowOrWorkerGlobalScope where
  toJSVal :: WindowOrWorkerGlobalScope -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WindowOrWorkerGlobalScope -> JSVal)
-> WindowOrWorkerGlobalScope
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowOrWorkerGlobalScope -> JSVal
unWindowOrWorkerGlobalScope
  {-# INLINE toJSVal #-}

instance FromJSVal WindowOrWorkerGlobalScope where
  fromJSVal :: JSVal -> JSM (Maybe WindowOrWorkerGlobalScope)
fromJSVal JSVal
v = (JSVal -> WindowOrWorkerGlobalScope)
-> Maybe JSVal -> Maybe WindowOrWorkerGlobalScope
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WindowOrWorkerGlobalScope
WindowOrWorkerGlobalScope (Maybe JSVal -> Maybe WindowOrWorkerGlobalScope)
-> JSM (Maybe JSVal) -> JSM (Maybe WindowOrWorkerGlobalScope)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WindowOrWorkerGlobalScope
fromJSValUnchecked = WindowOrWorkerGlobalScope -> JSM WindowOrWorkerGlobalScope
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WindowOrWorkerGlobalScope -> JSM WindowOrWorkerGlobalScope)
-> (JSVal -> WindowOrWorkerGlobalScope)
-> JSVal
-> JSM WindowOrWorkerGlobalScope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WindowOrWorkerGlobalScope
WindowOrWorkerGlobalScope
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WindowOrWorkerGlobalScope where
  makeObject :: WindowOrWorkerGlobalScope -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WindowOrWorkerGlobalScope -> JSVal)
-> WindowOrWorkerGlobalScope
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowOrWorkerGlobalScope -> JSVal
unWindowOrWorkerGlobalScope

class (IsGObject o) => IsWindowOrWorkerGlobalScope o
toWindowOrWorkerGlobalScope :: IsWindowOrWorkerGlobalScope o => o -> WindowOrWorkerGlobalScope
toWindowOrWorkerGlobalScope :: forall o.
IsWindowOrWorkerGlobalScope o =>
o -> WindowOrWorkerGlobalScope
toWindowOrWorkerGlobalScope = JSVal -> WindowOrWorkerGlobalScope
WindowOrWorkerGlobalScope (JSVal -> WindowOrWorkerGlobalScope)
-> (o -> JSVal) -> o -> WindowOrWorkerGlobalScope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsWindowOrWorkerGlobalScope WindowOrWorkerGlobalScope
instance IsGObject WindowOrWorkerGlobalScope where
  typeGType :: WindowOrWorkerGlobalScope -> JSM GType
typeGType WindowOrWorkerGlobalScope
_ = JSM GType
gTypeWindowOrWorkerGlobalScope
  {-# INLINE typeGType #-}

noWindowOrWorkerGlobalScope :: Maybe WindowOrWorkerGlobalScope
noWindowOrWorkerGlobalScope :: Maybe WindowOrWorkerGlobalScope
noWindowOrWorkerGlobalScope = Maybe WindowOrWorkerGlobalScope
forall a. Maybe a
Nothing
{-# INLINE noWindowOrWorkerGlobalScope #-}

gTypeWindowOrWorkerGlobalScope :: JSM GType
gTypeWindowOrWorkerGlobalScope :: JSM GType
gTypeWindowOrWorkerGlobalScope = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WindowOrWorkerGlobalScope"

-- | Functions for this inteface are in "JSDOM.Worker".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--     * "JSDOM.AbstractWorker"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/Worker Mozilla Worker documentation>
newtype Worker = Worker { Worker -> JSVal
unWorker :: JSVal }

instance PToJSVal Worker where
  pToJSVal :: Worker -> JSVal
pToJSVal = Worker -> JSVal
unWorker
  {-# INLINE pToJSVal #-}

instance PFromJSVal Worker where
  pFromJSVal :: JSVal -> Worker
pFromJSVal = JSVal -> Worker
Worker
  {-# INLINE pFromJSVal #-}

instance ToJSVal Worker where
  toJSVal :: Worker -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal) -> (Worker -> JSVal) -> Worker -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Worker -> JSVal
unWorker
  {-# INLINE toJSVal #-}

instance FromJSVal Worker where
  fromJSVal :: JSVal -> JSM (Maybe Worker)
fromJSVal JSVal
v = (JSVal -> Worker) -> Maybe JSVal -> Maybe Worker
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> Worker
Worker (Maybe JSVal -> Maybe Worker)
-> JSM (Maybe JSVal) -> JSM (Maybe Worker)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM Worker
fromJSValUnchecked = Worker -> JSM Worker
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (Worker -> JSM Worker) -> (JSVal -> Worker) -> JSVal -> JSM Worker
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Worker
Worker
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject Worker where
  makeObject :: Worker -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object) -> (Worker -> JSVal) -> Worker -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Worker -> JSVal
unWorker

instance IsEventTarget Worker
instance IsAbstractWorker Worker
instance IsGObject Worker where
  typeGType :: Worker -> JSM GType
typeGType Worker
_ = JSM GType
gTypeWorker
  {-# INLINE typeGType #-}

noWorker :: Maybe Worker
noWorker :: Maybe Worker
noWorker = Maybe Worker
forall a. Maybe a
Nothing
{-# INLINE noWorker #-}

gTypeWorker :: JSM GType
gTypeWorker :: JSM GType
gTypeWorker = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"Worker"

-- | Functions for this inteface are in "JSDOM.WorkerGlobalScope".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--     * "JSDOM.WindowOrWorkerGlobalScope"
--     * "JSDOM.GlobalPerformance"
--     * "JSDOM.GlobalCrypto"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WorkerGlobalScope Mozilla WorkerGlobalScope documentation>
newtype WorkerGlobalScope = WorkerGlobalScope { WorkerGlobalScope -> JSVal
unWorkerGlobalScope :: JSVal }

instance PToJSVal WorkerGlobalScope where
  pToJSVal :: WorkerGlobalScope -> JSVal
pToJSVal = WorkerGlobalScope -> JSVal
unWorkerGlobalScope
  {-# INLINE pToJSVal #-}

instance PFromJSVal WorkerGlobalScope where
  pFromJSVal :: JSVal -> WorkerGlobalScope
pFromJSVal = JSVal -> WorkerGlobalScope
WorkerGlobalScope
  {-# INLINE pFromJSVal #-}

instance ToJSVal WorkerGlobalScope where
  toJSVal :: WorkerGlobalScope -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WorkerGlobalScope -> JSVal) -> WorkerGlobalScope -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkerGlobalScope -> JSVal
unWorkerGlobalScope
  {-# INLINE toJSVal #-}

instance FromJSVal WorkerGlobalScope where
  fromJSVal :: JSVal -> JSM (Maybe WorkerGlobalScope)
fromJSVal JSVal
v = (JSVal -> WorkerGlobalScope)
-> Maybe JSVal -> Maybe WorkerGlobalScope
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WorkerGlobalScope
WorkerGlobalScope (Maybe JSVal -> Maybe WorkerGlobalScope)
-> JSM (Maybe JSVal) -> JSM (Maybe WorkerGlobalScope)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WorkerGlobalScope
fromJSValUnchecked = WorkerGlobalScope -> JSM WorkerGlobalScope
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WorkerGlobalScope -> JSM WorkerGlobalScope)
-> (JSVal -> WorkerGlobalScope) -> JSVal -> JSM WorkerGlobalScope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WorkerGlobalScope
WorkerGlobalScope
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WorkerGlobalScope where
  makeObject :: WorkerGlobalScope -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WorkerGlobalScope -> JSVal) -> WorkerGlobalScope -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkerGlobalScope -> JSVal
unWorkerGlobalScope

class (IsEventTarget o, IsWindowOrWorkerGlobalScope o, IsGlobalPerformance o, IsGlobalCrypto o, IsGObject o) => IsWorkerGlobalScope o
toWorkerGlobalScope :: IsWorkerGlobalScope o => o -> WorkerGlobalScope
toWorkerGlobalScope :: forall o. IsWorkerGlobalScope o => o -> WorkerGlobalScope
toWorkerGlobalScope = JSVal -> WorkerGlobalScope
WorkerGlobalScope (JSVal -> WorkerGlobalScope)
-> (o -> JSVal) -> o -> WorkerGlobalScope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsWorkerGlobalScope WorkerGlobalScope
instance IsEventTarget WorkerGlobalScope
instance IsWindowOrWorkerGlobalScope WorkerGlobalScope
instance IsGlobalPerformance WorkerGlobalScope
instance IsGlobalCrypto WorkerGlobalScope
instance IsGObject WorkerGlobalScope where
  typeGType :: WorkerGlobalScope -> JSM GType
typeGType WorkerGlobalScope
_ = JSM GType
gTypeWorkerGlobalScope
  {-# INLINE typeGType #-}

noWorkerGlobalScope :: Maybe WorkerGlobalScope
noWorkerGlobalScope :: Maybe WorkerGlobalScope
noWorkerGlobalScope = Maybe WorkerGlobalScope
forall a. Maybe a
Nothing
{-# INLINE noWorkerGlobalScope #-}

gTypeWorkerGlobalScope :: JSM GType
gTypeWorkerGlobalScope :: JSM GType
gTypeWorkerGlobalScope = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WorkerGlobalScope"

-- | Functions for this inteface are in "JSDOM.WorkerLocation".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WorkerLocation Mozilla WorkerLocation documentation>
newtype WorkerLocation = WorkerLocation { WorkerLocation -> JSVal
unWorkerLocation :: JSVal }

instance PToJSVal WorkerLocation where
  pToJSVal :: WorkerLocation -> JSVal
pToJSVal = WorkerLocation -> JSVal
unWorkerLocation
  {-# INLINE pToJSVal #-}

instance PFromJSVal WorkerLocation where
  pFromJSVal :: JSVal -> WorkerLocation
pFromJSVal = JSVal -> WorkerLocation
WorkerLocation
  {-# INLINE pFromJSVal #-}

instance ToJSVal WorkerLocation where
  toJSVal :: WorkerLocation -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WorkerLocation -> JSVal) -> WorkerLocation -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkerLocation -> JSVal
unWorkerLocation
  {-# INLINE toJSVal #-}

instance FromJSVal WorkerLocation where
  fromJSVal :: JSVal -> JSM (Maybe WorkerLocation)
fromJSVal JSVal
v = (JSVal -> WorkerLocation) -> Maybe JSVal -> Maybe WorkerLocation
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WorkerLocation
WorkerLocation (Maybe JSVal -> Maybe WorkerLocation)
-> JSM (Maybe JSVal) -> JSM (Maybe WorkerLocation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WorkerLocation
fromJSValUnchecked = WorkerLocation -> JSM WorkerLocation
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WorkerLocation -> JSM WorkerLocation)
-> (JSVal -> WorkerLocation) -> JSVal -> JSM WorkerLocation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WorkerLocation
WorkerLocation
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WorkerLocation where
  makeObject :: WorkerLocation -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WorkerLocation -> JSVal) -> WorkerLocation -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkerLocation -> JSVal
unWorkerLocation

instance IsGObject WorkerLocation where
  typeGType :: WorkerLocation -> JSM GType
typeGType WorkerLocation
_ = JSM GType
gTypeWorkerLocation
  {-# INLINE typeGType #-}

noWorkerLocation :: Maybe WorkerLocation
noWorkerLocation :: Maybe WorkerLocation
noWorkerLocation = Maybe WorkerLocation
forall a. Maybe a
Nothing
{-# INLINE noWorkerLocation #-}

gTypeWorkerLocation :: JSM GType
gTypeWorkerLocation :: JSM GType
gTypeWorkerLocation = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WorkerLocation"

-- | Functions for this inteface are in "JSDOM.WorkerNavigator".
-- Base interface functions are in:
--
--     * "JSDOM.NavigatorOnLine"
--     * "JSDOM.NavigatorLanguage"
--     * "JSDOM.NavigatorID"
--     * "JSDOM.NavigatorConcurrentHardware"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WorkerNavigator Mozilla WorkerNavigator documentation>
newtype WorkerNavigator = WorkerNavigator { WorkerNavigator -> JSVal
unWorkerNavigator :: JSVal }

instance PToJSVal WorkerNavigator where
  pToJSVal :: WorkerNavigator -> JSVal
pToJSVal = WorkerNavigator -> JSVal
unWorkerNavigator
  {-# INLINE pToJSVal #-}

instance PFromJSVal WorkerNavigator where
  pFromJSVal :: JSVal -> WorkerNavigator
pFromJSVal = JSVal -> WorkerNavigator
WorkerNavigator
  {-# INLINE pFromJSVal #-}

instance ToJSVal WorkerNavigator where
  toJSVal :: WorkerNavigator -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WorkerNavigator -> JSVal) -> WorkerNavigator -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkerNavigator -> JSVal
unWorkerNavigator
  {-# INLINE toJSVal #-}

instance FromJSVal WorkerNavigator where
  fromJSVal :: JSVal -> JSM (Maybe WorkerNavigator)
fromJSVal JSVal
v = (JSVal -> WorkerNavigator) -> Maybe JSVal -> Maybe WorkerNavigator
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WorkerNavigator
WorkerNavigator (Maybe JSVal -> Maybe WorkerNavigator)
-> JSM (Maybe JSVal) -> JSM (Maybe WorkerNavigator)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WorkerNavigator
fromJSValUnchecked = WorkerNavigator -> JSM WorkerNavigator
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WorkerNavigator -> JSM WorkerNavigator)
-> (JSVal -> WorkerNavigator) -> JSVal -> JSM WorkerNavigator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WorkerNavigator
WorkerNavigator
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WorkerNavigator where
  makeObject :: WorkerNavigator -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WorkerNavigator -> JSVal) -> WorkerNavigator -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkerNavigator -> JSVal
unWorkerNavigator

instance IsNavigatorOnLine WorkerNavigator
instance IsNavigatorLanguage WorkerNavigator
instance IsNavigatorID WorkerNavigator
instance IsNavigatorConcurrentHardware WorkerNavigator
instance IsGObject WorkerNavigator where
  typeGType :: WorkerNavigator -> JSM GType
typeGType WorkerNavigator
_ = JSM GType
gTypeWorkerNavigator
  {-# INLINE typeGType #-}

noWorkerNavigator :: Maybe WorkerNavigator
noWorkerNavigator :: Maybe WorkerNavigator
noWorkerNavigator = Maybe WorkerNavigator
forall a. Maybe a
Nothing
{-# INLINE noWorkerNavigator #-}

gTypeWorkerNavigator :: JSM GType
gTypeWorkerNavigator :: JSM GType
gTypeWorkerNavigator = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WorkerNavigator"

-- | Functions for this inteface are in "JSDOM.WritableStream".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/WritableStream Mozilla WritableStream documentation>
newtype WritableStream = WritableStream { WritableStream -> JSVal
unWritableStream :: JSVal }

instance PToJSVal WritableStream where
  pToJSVal :: WritableStream -> JSVal
pToJSVal = WritableStream -> JSVal
unWritableStream
  {-# INLINE pToJSVal #-}

instance PFromJSVal WritableStream where
  pFromJSVal :: JSVal -> WritableStream
pFromJSVal = JSVal -> WritableStream
WritableStream
  {-# INLINE pFromJSVal #-}

instance ToJSVal WritableStream where
  toJSVal :: WritableStream -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (WritableStream -> JSVal) -> WritableStream -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WritableStream -> JSVal
unWritableStream
  {-# INLINE toJSVal #-}

instance FromJSVal WritableStream where
  fromJSVal :: JSVal -> JSM (Maybe WritableStream)
fromJSVal JSVal
v = (JSVal -> WritableStream) -> Maybe JSVal -> Maybe WritableStream
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> WritableStream
WritableStream (Maybe JSVal -> Maybe WritableStream)
-> JSM (Maybe JSVal) -> JSM (Maybe WritableStream)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM WritableStream
fromJSValUnchecked = WritableStream -> JSM WritableStream
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (WritableStream -> JSM WritableStream)
-> (JSVal -> WritableStream) -> JSVal -> JSM WritableStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> WritableStream
WritableStream
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject WritableStream where
  makeObject :: WritableStream -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (WritableStream -> JSVal) -> WritableStream -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WritableStream -> JSVal
unWritableStream

instance IsGObject WritableStream where
  typeGType :: WritableStream -> JSM GType
typeGType WritableStream
_ = JSM GType
gTypeWritableStream
  {-# INLINE typeGType #-}

noWritableStream :: Maybe WritableStream
noWritableStream :: Maybe WritableStream
noWritableStream = Maybe WritableStream
forall a. Maybe a
Nothing
{-# INLINE noWritableStream #-}

gTypeWritableStream :: JSM GType
gTypeWritableStream :: JSM GType
gTypeWritableStream = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"WritableStream"

-- | Functions for this inteface are in "JSDOM.XMLDocument".
-- Base interface functions are in:
--
--     * "JSDOM.Document"
--     * "JSDOM.Node"
--     * "JSDOM.EventTarget"
--     * "JSDOM.GlobalEventHandlers"
--     * "JSDOM.DocumentOrShadowRoot"
--     * "JSDOM.NonElementParentNode"
--     * "JSDOM.ParentNode"
--     * "JSDOM.DocumentAndElementEventHandlers"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XMLDocument Mozilla XMLDocument documentation>
newtype XMLDocument = XMLDocument { XMLDocument -> JSVal
unXMLDocument :: JSVal }

instance PToJSVal XMLDocument where
  pToJSVal :: XMLDocument -> JSVal
pToJSVal = XMLDocument -> JSVal
unXMLDocument
  {-# INLINE pToJSVal #-}

instance PFromJSVal XMLDocument where
  pFromJSVal :: JSVal -> XMLDocument
pFromJSVal = JSVal -> XMLDocument
XMLDocument
  {-# INLINE pFromJSVal #-}

instance ToJSVal XMLDocument where
  toJSVal :: XMLDocument -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XMLDocument -> JSVal) -> XMLDocument -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLDocument -> JSVal
unXMLDocument
  {-# INLINE toJSVal #-}

instance FromJSVal XMLDocument where
  fromJSVal :: JSVal -> JSM (Maybe XMLDocument)
fromJSVal JSVal
v = (JSVal -> XMLDocument) -> Maybe JSVal -> Maybe XMLDocument
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XMLDocument
XMLDocument (Maybe JSVal -> Maybe XMLDocument)
-> JSM (Maybe JSVal) -> JSM (Maybe XMLDocument)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XMLDocument
fromJSValUnchecked = XMLDocument -> JSM XMLDocument
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XMLDocument -> JSM XMLDocument)
-> (JSVal -> XMLDocument) -> JSVal -> JSM XMLDocument
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XMLDocument
XMLDocument
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XMLDocument where
  makeObject :: XMLDocument -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XMLDocument -> JSVal) -> XMLDocument -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLDocument -> JSVal
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 :: XMLDocument -> JSM GType
typeGType XMLDocument
_ = JSM GType
gTypeXMLDocument
  {-# INLINE typeGType #-}

noXMLDocument :: Maybe XMLDocument
noXMLDocument :: Maybe XMLDocument
noXMLDocument = Maybe XMLDocument
forall a. Maybe a
Nothing
{-# INLINE noXMLDocument #-}

gTypeXMLDocument :: JSM GType
gTypeXMLDocument :: JSM GType
gTypeXMLDocument = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XMLDocument"

-- | Functions for this inteface are in "JSDOM.XMLHttpRequest".
-- Base interface functions are in:
--
--     * "JSDOM.XMLHttpRequestEventTarget"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XMLHttpRequest Mozilla XMLHttpRequest documentation>
newtype XMLHttpRequest = XMLHttpRequest { XMLHttpRequest -> JSVal
unXMLHttpRequest :: JSVal }

instance PToJSVal XMLHttpRequest where
  pToJSVal :: XMLHttpRequest -> JSVal
pToJSVal = XMLHttpRequest -> JSVal
unXMLHttpRequest
  {-# INLINE pToJSVal #-}

instance PFromJSVal XMLHttpRequest where
  pFromJSVal :: JSVal -> XMLHttpRequest
pFromJSVal = JSVal -> XMLHttpRequest
XMLHttpRequest
  {-# INLINE pFromJSVal #-}

instance ToJSVal XMLHttpRequest where
  toJSVal :: XMLHttpRequest -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XMLHttpRequest -> JSVal) -> XMLHttpRequest -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLHttpRequest -> JSVal
unXMLHttpRequest
  {-# INLINE toJSVal #-}

instance FromJSVal XMLHttpRequest where
  fromJSVal :: JSVal -> JSM (Maybe XMLHttpRequest)
fromJSVal JSVal
v = (JSVal -> XMLHttpRequest) -> Maybe JSVal -> Maybe XMLHttpRequest
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XMLHttpRequest
XMLHttpRequest (Maybe JSVal -> Maybe XMLHttpRequest)
-> JSM (Maybe JSVal) -> JSM (Maybe XMLHttpRequest)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XMLHttpRequest
fromJSValUnchecked = XMLHttpRequest -> JSM XMLHttpRequest
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XMLHttpRequest -> JSM XMLHttpRequest)
-> (JSVal -> XMLHttpRequest) -> JSVal -> JSM XMLHttpRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XMLHttpRequest
XMLHttpRequest
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XMLHttpRequest where
  makeObject :: XMLHttpRequest -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XMLHttpRequest -> JSVal) -> XMLHttpRequest -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLHttpRequest -> JSVal
unXMLHttpRequest

instance IsXMLHttpRequestEventTarget XMLHttpRequest
instance IsEventTarget XMLHttpRequest
instance IsGObject XMLHttpRequest where
  typeGType :: XMLHttpRequest -> JSM GType
typeGType XMLHttpRequest
_ = JSM GType
gTypeXMLHttpRequest
  {-# INLINE typeGType #-}

noXMLHttpRequest :: Maybe XMLHttpRequest
noXMLHttpRequest :: Maybe XMLHttpRequest
noXMLHttpRequest = Maybe XMLHttpRequest
forall a. Maybe a
Nothing
{-# INLINE noXMLHttpRequest #-}

gTypeXMLHttpRequest :: JSM GType
gTypeXMLHttpRequest :: JSM GType
gTypeXMLHttpRequest = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XMLHttpRequest"

-- | Functions for this inteface are in "JSDOM.XMLHttpRequestEventTarget".
-- Base interface functions are in:
--
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XMLHttpRequestEventTarget Mozilla XMLHttpRequestEventTarget documentation>
newtype XMLHttpRequestEventTarget = XMLHttpRequestEventTarget { XMLHttpRequestEventTarget -> JSVal
unXMLHttpRequestEventTarget :: JSVal }

instance PToJSVal XMLHttpRequestEventTarget where
  pToJSVal :: XMLHttpRequestEventTarget -> JSVal
pToJSVal = XMLHttpRequestEventTarget -> JSVal
unXMLHttpRequestEventTarget
  {-# INLINE pToJSVal #-}

instance PFromJSVal XMLHttpRequestEventTarget where
  pFromJSVal :: JSVal -> XMLHttpRequestEventTarget
pFromJSVal = JSVal -> XMLHttpRequestEventTarget
XMLHttpRequestEventTarget
  {-# INLINE pFromJSVal #-}

instance ToJSVal XMLHttpRequestEventTarget where
  toJSVal :: XMLHttpRequestEventTarget -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XMLHttpRequestEventTarget -> JSVal)
-> XMLHttpRequestEventTarget
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLHttpRequestEventTarget -> JSVal
unXMLHttpRequestEventTarget
  {-# INLINE toJSVal #-}

instance FromJSVal XMLHttpRequestEventTarget where
  fromJSVal :: JSVal -> JSM (Maybe XMLHttpRequestEventTarget)
fromJSVal JSVal
v = (JSVal -> XMLHttpRequestEventTarget)
-> Maybe JSVal -> Maybe XMLHttpRequestEventTarget
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XMLHttpRequestEventTarget
XMLHttpRequestEventTarget (Maybe JSVal -> Maybe XMLHttpRequestEventTarget)
-> JSM (Maybe JSVal) -> JSM (Maybe XMLHttpRequestEventTarget)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XMLHttpRequestEventTarget
fromJSValUnchecked = XMLHttpRequestEventTarget -> JSM XMLHttpRequestEventTarget
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XMLHttpRequestEventTarget -> JSM XMLHttpRequestEventTarget)
-> (JSVal -> XMLHttpRequestEventTarget)
-> JSVal
-> JSM XMLHttpRequestEventTarget
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XMLHttpRequestEventTarget
XMLHttpRequestEventTarget
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XMLHttpRequestEventTarget where
  makeObject :: XMLHttpRequestEventTarget -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XMLHttpRequestEventTarget -> JSVal)
-> XMLHttpRequestEventTarget
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLHttpRequestEventTarget -> JSVal
unXMLHttpRequestEventTarget

class (IsEventTarget o, IsGObject o) => IsXMLHttpRequestEventTarget o
toXMLHttpRequestEventTarget :: IsXMLHttpRequestEventTarget o => o -> XMLHttpRequestEventTarget
toXMLHttpRequestEventTarget :: forall o.
IsXMLHttpRequestEventTarget o =>
o -> XMLHttpRequestEventTarget
toXMLHttpRequestEventTarget = JSVal -> XMLHttpRequestEventTarget
XMLHttpRequestEventTarget (JSVal -> XMLHttpRequestEventTarget)
-> (o -> JSVal) -> o -> XMLHttpRequestEventTarget
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> JSVal
forall a b. Coercible a b => a -> b
coerce

instance IsXMLHttpRequestEventTarget XMLHttpRequestEventTarget
instance IsEventTarget XMLHttpRequestEventTarget
instance IsGObject XMLHttpRequestEventTarget where
  typeGType :: XMLHttpRequestEventTarget -> JSM GType
typeGType XMLHttpRequestEventTarget
_ = JSM GType
gTypeXMLHttpRequestEventTarget
  {-# INLINE typeGType #-}

noXMLHttpRequestEventTarget :: Maybe XMLHttpRequestEventTarget
noXMLHttpRequestEventTarget :: Maybe XMLHttpRequestEventTarget
noXMLHttpRequestEventTarget = Maybe XMLHttpRequestEventTarget
forall a. Maybe a
Nothing
{-# INLINE noXMLHttpRequestEventTarget #-}

gTypeXMLHttpRequestEventTarget :: JSM GType
gTypeXMLHttpRequestEventTarget :: JSM GType
gTypeXMLHttpRequestEventTarget = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XMLHttpRequestEventTarget"

-- | Functions for this inteface are in "JSDOM.XMLHttpRequestProgressEvent".
-- Base interface functions are in:
--
--     * "JSDOM.ProgressEvent"
--     * "JSDOM.Event"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XMLHttpRequestProgressEvent Mozilla XMLHttpRequestProgressEvent documentation>
newtype XMLHttpRequestProgressEvent = XMLHttpRequestProgressEvent { XMLHttpRequestProgressEvent -> JSVal
unXMLHttpRequestProgressEvent :: JSVal }

instance PToJSVal XMLHttpRequestProgressEvent where
  pToJSVal :: XMLHttpRequestProgressEvent -> JSVal
pToJSVal = XMLHttpRequestProgressEvent -> JSVal
unXMLHttpRequestProgressEvent
  {-# INLINE pToJSVal #-}

instance PFromJSVal XMLHttpRequestProgressEvent where
  pFromJSVal :: JSVal -> XMLHttpRequestProgressEvent
pFromJSVal = JSVal -> XMLHttpRequestProgressEvent
XMLHttpRequestProgressEvent
  {-# INLINE pFromJSVal #-}

instance ToJSVal XMLHttpRequestProgressEvent where
  toJSVal :: XMLHttpRequestProgressEvent -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XMLHttpRequestProgressEvent -> JSVal)
-> XMLHttpRequestProgressEvent
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLHttpRequestProgressEvent -> JSVal
unXMLHttpRequestProgressEvent
  {-# INLINE toJSVal #-}

instance FromJSVal XMLHttpRequestProgressEvent where
  fromJSVal :: JSVal -> JSM (Maybe XMLHttpRequestProgressEvent)
fromJSVal JSVal
v = (JSVal -> XMLHttpRequestProgressEvent)
-> Maybe JSVal -> Maybe XMLHttpRequestProgressEvent
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XMLHttpRequestProgressEvent
XMLHttpRequestProgressEvent (Maybe JSVal -> Maybe XMLHttpRequestProgressEvent)
-> JSM (Maybe JSVal) -> JSM (Maybe XMLHttpRequestProgressEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XMLHttpRequestProgressEvent
fromJSValUnchecked = XMLHttpRequestProgressEvent -> JSM XMLHttpRequestProgressEvent
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XMLHttpRequestProgressEvent -> JSM XMLHttpRequestProgressEvent)
-> (JSVal -> XMLHttpRequestProgressEvent)
-> JSVal
-> JSM XMLHttpRequestProgressEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XMLHttpRequestProgressEvent
XMLHttpRequestProgressEvent
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XMLHttpRequestProgressEvent where
  makeObject :: XMLHttpRequestProgressEvent -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XMLHttpRequestProgressEvent -> JSVal)
-> XMLHttpRequestProgressEvent
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLHttpRequestProgressEvent -> JSVal
unXMLHttpRequestProgressEvent

instance IsProgressEvent XMLHttpRequestProgressEvent
instance IsEvent XMLHttpRequestProgressEvent
instance IsGObject XMLHttpRequestProgressEvent where
  typeGType :: XMLHttpRequestProgressEvent -> JSM GType
typeGType XMLHttpRequestProgressEvent
_ = JSM GType
gTypeXMLHttpRequestProgressEvent
  {-# INLINE typeGType #-}

noXMLHttpRequestProgressEvent :: Maybe XMLHttpRequestProgressEvent
noXMLHttpRequestProgressEvent :: Maybe XMLHttpRequestProgressEvent
noXMLHttpRequestProgressEvent = Maybe XMLHttpRequestProgressEvent
forall a. Maybe a
Nothing
{-# INLINE noXMLHttpRequestProgressEvent #-}

gTypeXMLHttpRequestProgressEvent :: JSM GType
gTypeXMLHttpRequestProgressEvent :: JSM GType
gTypeXMLHttpRequestProgressEvent = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XMLHttpRequestProgressEvent"

-- | Functions for this inteface are in "JSDOM.XMLHttpRequestUpload".
-- Base interface functions are in:
--
--     * "JSDOM.XMLHttpRequestEventTarget"
--     * "JSDOM.EventTarget"
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XMLHttpRequestUpload Mozilla XMLHttpRequestUpload documentation>
newtype XMLHttpRequestUpload = XMLHttpRequestUpload { XMLHttpRequestUpload -> JSVal
unXMLHttpRequestUpload :: JSVal }

instance PToJSVal XMLHttpRequestUpload where
  pToJSVal :: XMLHttpRequestUpload -> JSVal
pToJSVal = XMLHttpRequestUpload -> JSVal
unXMLHttpRequestUpload
  {-# INLINE pToJSVal #-}

instance PFromJSVal XMLHttpRequestUpload where
  pFromJSVal :: JSVal -> XMLHttpRequestUpload
pFromJSVal = JSVal -> XMLHttpRequestUpload
XMLHttpRequestUpload
  {-# INLINE pFromJSVal #-}

instance ToJSVal XMLHttpRequestUpload where
  toJSVal :: XMLHttpRequestUpload -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XMLHttpRequestUpload -> JSVal)
-> XMLHttpRequestUpload
-> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLHttpRequestUpload -> JSVal
unXMLHttpRequestUpload
  {-# INLINE toJSVal #-}

instance FromJSVal XMLHttpRequestUpload where
  fromJSVal :: JSVal -> JSM (Maybe XMLHttpRequestUpload)
fromJSVal JSVal
v = (JSVal -> XMLHttpRequestUpload)
-> Maybe JSVal -> Maybe XMLHttpRequestUpload
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XMLHttpRequestUpload
XMLHttpRequestUpload (Maybe JSVal -> Maybe XMLHttpRequestUpload)
-> JSM (Maybe JSVal) -> JSM (Maybe XMLHttpRequestUpload)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XMLHttpRequestUpload
fromJSValUnchecked = XMLHttpRequestUpload -> JSM XMLHttpRequestUpload
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XMLHttpRequestUpload -> JSM XMLHttpRequestUpload)
-> (JSVal -> XMLHttpRequestUpload)
-> JSVal
-> JSM XMLHttpRequestUpload
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XMLHttpRequestUpload
XMLHttpRequestUpload
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XMLHttpRequestUpload where
  makeObject :: XMLHttpRequestUpload -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XMLHttpRequestUpload -> JSVal)
-> XMLHttpRequestUpload
-> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLHttpRequestUpload -> JSVal
unXMLHttpRequestUpload

instance IsXMLHttpRequestEventTarget XMLHttpRequestUpload
instance IsEventTarget XMLHttpRequestUpload
instance IsGObject XMLHttpRequestUpload where
  typeGType :: XMLHttpRequestUpload -> JSM GType
typeGType XMLHttpRequestUpload
_ = JSM GType
gTypeXMLHttpRequestUpload
  {-# INLINE typeGType #-}

noXMLHttpRequestUpload :: Maybe XMLHttpRequestUpload
noXMLHttpRequestUpload :: Maybe XMLHttpRequestUpload
noXMLHttpRequestUpload = Maybe XMLHttpRequestUpload
forall a. Maybe a
Nothing
{-# INLINE noXMLHttpRequestUpload #-}

gTypeXMLHttpRequestUpload :: JSM GType
gTypeXMLHttpRequestUpload :: JSM GType
gTypeXMLHttpRequestUpload = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XMLHttpRequestUpload"

-- | Functions for this inteface are in "JSDOM.XMLSerializer".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XMLSerializer Mozilla XMLSerializer documentation>
newtype XMLSerializer = XMLSerializer { XMLSerializer -> JSVal
unXMLSerializer :: JSVal }

instance PToJSVal XMLSerializer where
  pToJSVal :: XMLSerializer -> JSVal
pToJSVal = XMLSerializer -> JSVal
unXMLSerializer
  {-# INLINE pToJSVal #-}

instance PFromJSVal XMLSerializer where
  pFromJSVal :: JSVal -> XMLSerializer
pFromJSVal = JSVal -> XMLSerializer
XMLSerializer
  {-# INLINE pFromJSVal #-}

instance ToJSVal XMLSerializer where
  toJSVal :: XMLSerializer -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XMLSerializer -> JSVal) -> XMLSerializer -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLSerializer -> JSVal
unXMLSerializer
  {-# INLINE toJSVal #-}

instance FromJSVal XMLSerializer where
  fromJSVal :: JSVal -> JSM (Maybe XMLSerializer)
fromJSVal JSVal
v = (JSVal -> XMLSerializer) -> Maybe JSVal -> Maybe XMLSerializer
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XMLSerializer
XMLSerializer (Maybe JSVal -> Maybe XMLSerializer)
-> JSM (Maybe JSVal) -> JSM (Maybe XMLSerializer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XMLSerializer
fromJSValUnchecked = XMLSerializer -> JSM XMLSerializer
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XMLSerializer -> JSM XMLSerializer)
-> (JSVal -> XMLSerializer) -> JSVal -> JSM XMLSerializer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XMLSerializer
XMLSerializer
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XMLSerializer where
  makeObject :: XMLSerializer -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XMLSerializer -> JSVal) -> XMLSerializer -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XMLSerializer -> JSVal
unXMLSerializer

instance IsGObject XMLSerializer where
  typeGType :: XMLSerializer -> JSM GType
typeGType XMLSerializer
_ = JSM GType
gTypeXMLSerializer
  {-# INLINE typeGType #-}

noXMLSerializer :: Maybe XMLSerializer
noXMLSerializer :: Maybe XMLSerializer
noXMLSerializer = Maybe XMLSerializer
forall a. Maybe a
Nothing
{-# INLINE noXMLSerializer #-}

gTypeXMLSerializer :: JSM GType
gTypeXMLSerializer :: JSM GType
gTypeXMLSerializer = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XMLSerializer"

-- | Functions for this inteface are in "JSDOM.XPathEvaluator".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XPathEvaluator Mozilla XPathEvaluator documentation>
newtype XPathEvaluator = XPathEvaluator { XPathEvaluator -> JSVal
unXPathEvaluator :: JSVal }

instance PToJSVal XPathEvaluator where
  pToJSVal :: XPathEvaluator -> JSVal
pToJSVal = XPathEvaluator -> JSVal
unXPathEvaluator
  {-# INLINE pToJSVal #-}

instance PFromJSVal XPathEvaluator where
  pFromJSVal :: JSVal -> XPathEvaluator
pFromJSVal = JSVal -> XPathEvaluator
XPathEvaluator
  {-# INLINE pFromJSVal #-}

instance ToJSVal XPathEvaluator where
  toJSVal :: XPathEvaluator -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XPathEvaluator -> JSVal) -> XPathEvaluator -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPathEvaluator -> JSVal
unXPathEvaluator
  {-# INLINE toJSVal #-}

instance FromJSVal XPathEvaluator where
  fromJSVal :: JSVal -> JSM (Maybe XPathEvaluator)
fromJSVal JSVal
v = (JSVal -> XPathEvaluator) -> Maybe JSVal -> Maybe XPathEvaluator
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XPathEvaluator
XPathEvaluator (Maybe JSVal -> Maybe XPathEvaluator)
-> JSM (Maybe JSVal) -> JSM (Maybe XPathEvaluator)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XPathEvaluator
fromJSValUnchecked = XPathEvaluator -> JSM XPathEvaluator
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XPathEvaluator -> JSM XPathEvaluator)
-> (JSVal -> XPathEvaluator) -> JSVal -> JSM XPathEvaluator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XPathEvaluator
XPathEvaluator
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XPathEvaluator where
  makeObject :: XPathEvaluator -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XPathEvaluator -> JSVal) -> XPathEvaluator -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPathEvaluator -> JSVal
unXPathEvaluator

instance IsGObject XPathEvaluator where
  typeGType :: XPathEvaluator -> JSM GType
typeGType XPathEvaluator
_ = JSM GType
gTypeXPathEvaluator
  {-# INLINE typeGType #-}

noXPathEvaluator :: Maybe XPathEvaluator
noXPathEvaluator :: Maybe XPathEvaluator
noXPathEvaluator = Maybe XPathEvaluator
forall a. Maybe a
Nothing
{-# INLINE noXPathEvaluator #-}

gTypeXPathEvaluator :: JSM GType
gTypeXPathEvaluator :: JSM GType
gTypeXPathEvaluator = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XPathEvaluator"

-- | Functions for this inteface are in "JSDOM.XPathException".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XPathException Mozilla XPathException documentation>
newtype XPathException = XPathException { XPathException -> JSVal
unXPathException :: JSVal }

instance PToJSVal XPathException where
  pToJSVal :: XPathException -> JSVal
pToJSVal = XPathException -> JSVal
unXPathException
  {-# INLINE pToJSVal #-}

instance PFromJSVal XPathException where
  pFromJSVal :: JSVal -> XPathException
pFromJSVal = JSVal -> XPathException
XPathException
  {-# INLINE pFromJSVal #-}

instance ToJSVal XPathException where
  toJSVal :: XPathException -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XPathException -> JSVal) -> XPathException -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPathException -> JSVal
unXPathException
  {-# INLINE toJSVal #-}

instance FromJSVal XPathException where
  fromJSVal :: JSVal -> JSM (Maybe XPathException)
fromJSVal JSVal
v = (JSVal -> XPathException) -> Maybe JSVal -> Maybe XPathException
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XPathException
XPathException (Maybe JSVal -> Maybe XPathException)
-> JSM (Maybe JSVal) -> JSM (Maybe XPathException)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XPathException
fromJSValUnchecked = XPathException -> JSM XPathException
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XPathException -> JSM XPathException)
-> (JSVal -> XPathException) -> JSVal -> JSM XPathException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XPathException
XPathException
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XPathException where
  makeObject :: XPathException -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XPathException -> JSVal) -> XPathException -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPathException -> JSVal
unXPathException

instance IsGObject XPathException where
  typeGType :: XPathException -> JSM GType
typeGType XPathException
_ = JSM GType
gTypeXPathException
  {-# INLINE typeGType #-}

noXPathException :: Maybe XPathException
noXPathException :: Maybe XPathException
noXPathException = Maybe XPathException
forall a. Maybe a
Nothing
{-# INLINE noXPathException #-}

gTypeXPathException :: JSM GType
gTypeXPathException :: JSM GType
gTypeXPathException = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XPathException"

-- | Functions for this inteface are in "JSDOM.XPathExpression".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XPathExpression Mozilla XPathExpression documentation>
newtype XPathExpression = XPathExpression { XPathExpression -> JSVal
unXPathExpression :: JSVal }

instance PToJSVal XPathExpression where
  pToJSVal :: XPathExpression -> JSVal
pToJSVal = XPathExpression -> JSVal
unXPathExpression
  {-# INLINE pToJSVal #-}

instance PFromJSVal XPathExpression where
  pFromJSVal :: JSVal -> XPathExpression
pFromJSVal = JSVal -> XPathExpression
XPathExpression
  {-# INLINE pFromJSVal #-}

instance ToJSVal XPathExpression where
  toJSVal :: XPathExpression -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XPathExpression -> JSVal) -> XPathExpression -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPathExpression -> JSVal
unXPathExpression
  {-# INLINE toJSVal #-}

instance FromJSVal XPathExpression where
  fromJSVal :: JSVal -> JSM (Maybe XPathExpression)
fromJSVal JSVal
v = (JSVal -> XPathExpression) -> Maybe JSVal -> Maybe XPathExpression
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XPathExpression
XPathExpression (Maybe JSVal -> Maybe XPathExpression)
-> JSM (Maybe JSVal) -> JSM (Maybe XPathExpression)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XPathExpression
fromJSValUnchecked = XPathExpression -> JSM XPathExpression
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XPathExpression -> JSM XPathExpression)
-> (JSVal -> XPathExpression) -> JSVal -> JSM XPathExpression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XPathExpression
XPathExpression
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XPathExpression where
  makeObject :: XPathExpression -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XPathExpression -> JSVal) -> XPathExpression -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPathExpression -> JSVal
unXPathExpression

instance IsGObject XPathExpression where
  typeGType :: XPathExpression -> JSM GType
typeGType XPathExpression
_ = JSM GType
gTypeXPathExpression
  {-# INLINE typeGType #-}

noXPathExpression :: Maybe XPathExpression
noXPathExpression :: Maybe XPathExpression
noXPathExpression = Maybe XPathExpression
forall a. Maybe a
Nothing
{-# INLINE noXPathExpression #-}

gTypeXPathExpression :: JSM GType
gTypeXPathExpression :: JSM GType
gTypeXPathExpression = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XPathExpression"

-- | Functions for this inteface are in "JSDOM.XPathNSResolver".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XPathNSResolver Mozilla XPathNSResolver documentation>
newtype XPathNSResolver = XPathNSResolver { XPathNSResolver -> JSVal
unXPathNSResolver :: JSVal }

instance PToJSVal XPathNSResolver where
  pToJSVal :: XPathNSResolver -> JSVal
pToJSVal = XPathNSResolver -> JSVal
unXPathNSResolver
  {-# INLINE pToJSVal #-}

instance PFromJSVal XPathNSResolver where
  pFromJSVal :: JSVal -> XPathNSResolver
pFromJSVal = JSVal -> XPathNSResolver
XPathNSResolver
  {-# INLINE pFromJSVal #-}

instance ToJSVal XPathNSResolver where
  toJSVal :: XPathNSResolver -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XPathNSResolver -> JSVal) -> XPathNSResolver -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPathNSResolver -> JSVal
unXPathNSResolver
  {-# INLINE toJSVal #-}

instance FromJSVal XPathNSResolver where
  fromJSVal :: JSVal -> JSM (Maybe XPathNSResolver)
fromJSVal JSVal
v = (JSVal -> XPathNSResolver) -> Maybe JSVal -> Maybe XPathNSResolver
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XPathNSResolver
XPathNSResolver (Maybe JSVal -> Maybe XPathNSResolver)
-> JSM (Maybe JSVal) -> JSM (Maybe XPathNSResolver)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XPathNSResolver
fromJSValUnchecked = XPathNSResolver -> JSM XPathNSResolver
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XPathNSResolver -> JSM XPathNSResolver)
-> (JSVal -> XPathNSResolver) -> JSVal -> JSM XPathNSResolver
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XPathNSResolver
XPathNSResolver
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XPathNSResolver where
  makeObject :: XPathNSResolver -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XPathNSResolver -> JSVal) -> XPathNSResolver -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPathNSResolver -> JSVal
unXPathNSResolver

instance IsGObject XPathNSResolver where
  typeGType :: XPathNSResolver -> JSM GType
typeGType XPathNSResolver
_ = JSM GType
gTypeXPathNSResolver
  {-# INLINE typeGType #-}

noXPathNSResolver :: Maybe XPathNSResolver
noXPathNSResolver :: Maybe XPathNSResolver
noXPathNSResolver = Maybe XPathNSResolver
forall a. Maybe a
Nothing
{-# INLINE noXPathNSResolver #-}

gTypeXPathNSResolver :: JSM GType
gTypeXPathNSResolver :: JSM GType
gTypeXPathNSResolver = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XPathNSResolver"

-- | Functions for this inteface are in "JSDOM.XPathResult".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XPathResult Mozilla XPathResult documentation>
newtype XPathResult = XPathResult { XPathResult -> JSVal
unXPathResult :: JSVal }

instance PToJSVal XPathResult where
  pToJSVal :: XPathResult -> JSVal
pToJSVal = XPathResult -> JSVal
unXPathResult
  {-# INLINE pToJSVal #-}

instance PFromJSVal XPathResult where
  pFromJSVal :: JSVal -> XPathResult
pFromJSVal = JSVal -> XPathResult
XPathResult
  {-# INLINE pFromJSVal #-}

instance ToJSVal XPathResult where
  toJSVal :: XPathResult -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XPathResult -> JSVal) -> XPathResult -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPathResult -> JSVal
unXPathResult
  {-# INLINE toJSVal #-}

instance FromJSVal XPathResult where
  fromJSVal :: JSVal -> JSM (Maybe XPathResult)
fromJSVal JSVal
v = (JSVal -> XPathResult) -> Maybe JSVal -> Maybe XPathResult
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XPathResult
XPathResult (Maybe JSVal -> Maybe XPathResult)
-> JSM (Maybe JSVal) -> JSM (Maybe XPathResult)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XPathResult
fromJSValUnchecked = XPathResult -> JSM XPathResult
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XPathResult -> JSM XPathResult)
-> (JSVal -> XPathResult) -> JSVal -> JSM XPathResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XPathResult
XPathResult
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XPathResult where
  makeObject :: XPathResult -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XPathResult -> JSVal) -> XPathResult -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPathResult -> JSVal
unXPathResult

instance IsGObject XPathResult where
  typeGType :: XPathResult -> JSM GType
typeGType XPathResult
_ = JSM GType
gTypeXPathResult
  {-# INLINE typeGType #-}

noXPathResult :: Maybe XPathResult
noXPathResult :: Maybe XPathResult
noXPathResult = Maybe XPathResult
forall a. Maybe a
Nothing
{-# INLINE noXPathResult #-}

gTypeXPathResult :: JSM GType
gTypeXPathResult :: JSM GType
gTypeXPathResult = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XPathResult"

-- | Functions for this inteface are in "JSDOM.XSLTProcessor".
--
-- <https://developer.mozilla.org/en-US/docs/Web/API/XSLTProcessor Mozilla XSLTProcessor documentation>
newtype XSLTProcessor = XSLTProcessor { XSLTProcessor -> JSVal
unXSLTProcessor :: JSVal }

instance PToJSVal XSLTProcessor where
  pToJSVal :: XSLTProcessor -> JSVal
pToJSVal = XSLTProcessor -> JSVal
unXSLTProcessor
  {-# INLINE pToJSVal #-}

instance PFromJSVal XSLTProcessor where
  pFromJSVal :: JSVal -> XSLTProcessor
pFromJSVal = JSVal -> XSLTProcessor
XSLTProcessor
  {-# INLINE pFromJSVal #-}

instance ToJSVal XSLTProcessor where
  toJSVal :: XSLTProcessor -> JSM JSVal
toJSVal = JSVal -> JSM JSVal
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (JSVal -> JSM JSVal)
-> (XSLTProcessor -> JSVal) -> XSLTProcessor -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XSLTProcessor -> JSVal
unXSLTProcessor
  {-# INLINE toJSVal #-}

instance FromJSVal XSLTProcessor where
  fromJSVal :: JSVal -> JSM (Maybe XSLTProcessor)
fromJSVal JSVal
v = (JSVal -> XSLTProcessor) -> Maybe JSVal -> Maybe XSLTProcessor
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSVal -> XSLTProcessor
XSLTProcessor (Maybe JSVal -> Maybe XSLTProcessor)
-> JSM (Maybe JSVal) -> JSM (Maybe XSLTProcessor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> JSVal -> JSM (Maybe JSVal)
forall value. ToJSVal value => value -> JSM (Maybe JSVal)
maybeNullOrUndefined JSVal
v
  {-# INLINE fromJSVal #-}
  fromJSValUnchecked :: JSVal -> JSM XSLTProcessor
fromJSValUnchecked = XSLTProcessor -> JSM XSLTProcessor
forall a. a -> JSM a
forall (m :: * -> *) a. Monad m => a -> m a
return (XSLTProcessor -> JSM XSLTProcessor)
-> (JSVal -> XSLTProcessor) -> JSVal -> JSM XSLTProcessor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> XSLTProcessor
XSLTProcessor
  {-# INLINE fromJSValUnchecked #-}

instance MakeObject XSLTProcessor where
  makeObject :: XSLTProcessor -> JSM Object
makeObject = JSVal -> JSM Object
forall this. MakeObject this => this -> JSM Object
makeObject (JSVal -> JSM Object)
-> (XSLTProcessor -> JSVal) -> XSLTProcessor -> JSM Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XSLTProcessor -> JSVal
unXSLTProcessor

instance IsGObject XSLTProcessor where
  typeGType :: XSLTProcessor -> JSM GType
typeGType XSLTProcessor
_ = JSM GType
gTypeXSLTProcessor
  {-# INLINE typeGType #-}

noXSLTProcessor :: Maybe XSLTProcessor
noXSLTProcessor :: Maybe XSLTProcessor
noXSLTProcessor = Maybe XSLTProcessor
forall a. Maybe a
Nothing
{-# INLINE noXSLTProcessor #-}

gTypeXSLTProcessor :: JSM GType
gTypeXSLTProcessor :: JSM GType
gTypeXSLTProcessor = Object -> GType
GType (Object -> GType) -> (JSVal -> Object) -> JSVal -> GType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSVal -> Object
Object (JSVal -> GType) -> JSM JSVal -> JSM GType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"XSLTProcessor"